Mercurial > repos > proteore > proteore_clusterprofiler
changeset 7:4609346d8108 draft
planemo upload commit 9af2cf12c26c94e7206751ccf101a3368f92d0ba
author | proteore |
---|---|
date | Tue, 18 Dec 2018 09:21:32 -0500 |
parents | 5e16cec55146 |
children | b29255864039 |
files | GO-enrich.R README.rst cluster_profiler.xml test-data/EGO_BP_bar-plot test-data/EGO_BP_dot-plot test-data/EGO_CC_bar-plot test-data/EGO_CC_dot-plot test-data/GGO.CC.png test-data/GGO_BP_bar-plot test-data/GGO_CC_bar-plot test-data/GGO_MF_bar-plot test-data/background_ids.txt test-data/clusterProfiler_diagram_outputs__GGO.CC.png test-data/clusterProfiler_text_output.tabular test-data/cluster_profiler_EGO_BP.csv test-data/cluster_profiler_EGO_CC.csv test-data/cluster_profiler_EGO_MF.csv test-data/cluster_profiler_GGO_BP.csv test-data/cluster_profiler_GGO_CC.csv test-data/cluster_profiler_GGO_MF.csv test-data/input_id_list.csv test-data/input_test.txt test-data/log.txt test-data/mouse_geneID.txt test-data/universe.csv |
diffstat | 24 files changed, 24011 insertions(+), 567 deletions(-) [+] |
line wrap: on
line diff
--- a/GO-enrich.R Thu Mar 29 11:43:28 2018 -0400 +++ b/GO-enrich.R Tue Dec 18 09:21:32 2018 -0500 @@ -1,27 +1,47 @@ -library(clusterProfiler) - -#library(org.Sc.sgd.db) -library(org.Hs.eg.db) -library(org.Mm.eg.db) +options(warn=-1) #TURN OFF WARNINGS !!!!!! +suppressMessages(library(clusterProfiler,quietly = TRUE)) # Read file and return file content as data.frame -readfile = function(filename, header) { - if (header == "true") { - # Read only first line of the file as header: - headers <- read.table(filename, nrows = 1, header = FALSE, sep = "\t", stringsAsFactors = FALSE, fill = TRUE, na.strings=c("", "NA"), blank.lines.skip = TRUE, quote = "") - #Read the data of the files (skipping the first row) - file <- read.table(filename, skip = 1, header = FALSE, sep = "\t", stringsAsFactors = FALSE, fill = TRUE, na.strings=c("", "NA"), blank.lines.skip = TRUE, quote = "") - # Remove empty rows +read_file <- function(path,header){ + file <- try(read.csv(path,header=header, sep="\t",stringsAsFactors = FALSE, quote="",check.names = F),silent=TRUE) + if (inherits(file,"try-error")){ + stop("File not found !") + }else{ file <- file[!apply(is.na(file) | file == "", 1, all), , drop=FALSE] - #And assign the header to the data - names(file) <- headers + return(file) } - else { - file <- read.table(filename, header = FALSE, sep = "\t", stringsAsFactors = FALSE, fill = TRUE, na.strings=c("", "NA"), blank.lines.skip = TRUE, quote = "") - # Remove empty rows - file <- file[!apply(is.na(file) | file == "", 1, all), , drop=FALSE] +} + +#return the number of character from the longest description found (from the 10 first) +max_str_length_10_first <- function(vector){ + vector <- as.vector(vector) + nb_description = length(vector) + if (nb_description >= 10){nb_description=10} + return(max(nchar(vector[1:nb_description]))) +} + +str2bool <- function(x){ + if (any(is.element(c("t","true"),tolower(x)))){ + return (TRUE) + }else if (any(is.element(c("f","false"),tolower(x)))){ + return (FALSE) + }else{ + return(NULL) } - return(file) +} + +#used before the limit was set to 50 characters +width_by_max_char <- function (nb_max_char) { + if (nb_max_char < 50 ){ + width=600 + } else if (nb_max_char < 75) { + width=800 + } else if (nb_max_char < 100) { + width=900 + } else { + width=1000 + } + return (width) } repartition.GO <- function(geneid, orgdb, ontology, level=3, readable=TRUE) { @@ -30,37 +50,71 @@ ont=ontology, level=level, readable=TRUE) - name <- paste("GGO.", ontology, ".png", sep = "") - png(name) - p <- barplot(ggo, showCategory=10) - print(p) - dev.off() - return(ggo) + + if (length(ggo@result$ID) > 0 ) { + ggo@result$Description <- sapply(as.vector(ggo@result$Description), function(x) {ifelse(nchar(x)>50, substr(x,1,50),x)},USE.NAMES = FALSE) + #nb_max_char = max_str_length_10_first(ggo$Description) + #width = width_by_max_char(nb_max_char) + name <- paste("GGO_", ontology, "_bar-plot", sep = "") + png(name,height = 720, width = 600) + p <- barplot(ggo, showCategory=10) + print(p) + dev.off() + ggo <- as.data.frame(ggo) + return(ggo) + } } # GO over-representation test -enrich.GO <- function(geneid, universe, orgdb, ontology, pval_cutoff, qval_cutoff) { +enrich.GO <- function(geneid, universe, orgdb, ontology, pval_cutoff, qval_cutoff,plot) { ego<-enrichGO(gene=geneid, universe=universe, OrgDb=orgdb, - keytype="ENTREZID", ont=ontology, pAdjustMethod="BH", pvalueCutoff=pval_cutoff, qvalueCutoff=qval_cutoff, readable=TRUE) + # Plot bar & dot plots - bar_name <- paste("EGO.", ontology, ".bar.png", sep = "") - png(bar_name) - p <- barplot(ego) - print(p) - dev.off() - dot_name <- paste("EGO.", ontology, ".dot.png", sep = "") - png(dot_name) - p <- dotplot(ego, showCategory=10) - print(p) - dev.off() - return(ego) + #if there are enriched GopTerms + if (length(ego$ID)>0){ + + ego@result$Description <- sapply(ego@result$Description, function(x) {ifelse(nchar(x)>50, substr(x,1,50),x)},USE.NAMES = FALSE) + #nb_max_char = max_str_length_10_first(ego$Description) + #width = width_by_max_char(nb_max_char) + + if ("dotplot" %in% plot ){ + dot_name <- paste("EGO_", ontology, "_dot-plot", sep = "") + png(dot_name,height = 720, width = 600) + p <- dotplot(ego, showCategory=10) + print(p) + dev.off() + } + + if ("barplot" %in% plot ){ + bar_name <- paste("EGO_", ontology, "_bar-plot", sep = "") + png(bar_name,height = 720, width = 600) + p <- barplot(ego, showCategory=10) + print(p) + dev.off() + + } + ego <- as.data.frame(ego) + return(ego) + } else { + warning(paste("No Go terms enriched (EGO) found for ",ontology,"ontology"),immediate. = TRUE,noBreaks. = TRUE,call. = FALSE) + } +} + +check_ids <- function(vector,type) { + uniprot_pattern = "^([OPQ][0-9][A-Z0-9]{3}[0-9]|[A-NR-Z][0-9]([A-Z][A-Z0-9]{2}[0-9]){1,2})$" + entrez_id = "^([0-9]+|[A-Z]{1,2}_[0-9]+|[A-Z]{1,2}_[A-Z]{1,4}[0-9]+)$" + if (type == "entrez") + return(grepl(entrez_id,vector)) + else if (type == "uniprot") { + return(grepl(uniprot_pattern,vector)) + } } clusterProfiler = function() { @@ -89,7 +143,8 @@ --level: 1-3 --pval_cutoff --qval_cutoff - --text_output: text output filename \n") + --text_output: text output filename + --plot : type of visualization, dotplot or/and barplot \n") q(save="no") } # Parse arguments @@ -97,66 +152,66 @@ argsDF <- as.data.frame(do.call("rbind", parseArgs(args))) args <- as.list(as.character(argsDF$V2)) names(args) <- argsDF$V1 - #print(args) - + plot = unlist(strsplit(args$plot,",")) + go_represent=str2bool(args$go_represent) + go_enrich=str2bool(args$go_enrich) + + #save(args,file="/home/dchristiany/proteore_project/ProteoRE/tools/cluster_profiler/args.Rda") + #load("/home/dchristiany/proteore_project/ProteoRE/tools/cluster_profiler/args.Rda") + + suppressMessages(library(args$species, character.only = TRUE, quietly = TRUE)) + # Extract OrgDb - if (args$species=="human") { + if (args$species=="org.Hs.eg.db") { orgdb<-org.Hs.eg.db - } - else if (args$species=="mouse") { + } else if (args$species=="org.Mm.eg.db") { orgdb<-org.Mm.eg.db - } - else if (args$species=="rat") { + } else if (args$species=="org.Rn.eg.db") { orgdb<-org.Rn.eg.db } # Extract input IDs input_type = args$input_type + id_type = args$id_type + if (input_type == "text") { input = strsplit(args$input, "[ \t\n]+")[[1]] - } - else if (input_type == "file") { + } else if (input_type == "file") { filename = args$input ncol = args$ncol # Check ncol if (! as.numeric(gsub("c", "", ncol)) %% 1 == 0) { stop("Please enter the right format for column number: c[number]") - } - else { + } else { ncol = as.numeric(gsub("c", "", ncol)) } - header = args$header - # Get file content - file = readfile(filename, header) - # Extract Protein IDs list - input = c() - for (row in as.character(file[,ncol])) { - input = c(input, strsplit(row, ";")[[1]][1]) - } + header = str2bool(args$header) # Get file content + file = read_file(filename, header) # Extract Protein IDs list + input = unlist(sapply(as.character(file[,ncol]),function(x) rapply(strsplit(x,";"),c),USE.NAMES = FALSE)) } - id_type = args$id_type + + ## Get input gene list from input IDs #ID format Conversion #This case : from UNIPROT (protein id) to ENTREZ (gene id) #bitr = conversion function from clusterProfiler - if (id_type=="Uniprot") { + if (id_type=="Uniprot" & any(check_ids(input,"uniprot"))) { + any(check_ids(input,"uniprot")) idFrom<-"UNIPROT" idTo<-"ENTREZID" - gene<-bitr(input, fromType=idFrom, toType=idTo, OrgDb=orgdb) + suppressMessages(gene<-bitr(input, fromType=idFrom, toType=idTo, OrgDb=orgdb)) gene<-unique(gene$ENTREZID) - } - else if (id_type=="Entrez") { + } else if (id_type=="Entrez" & any(check_ids(input,"entrez"))) { gene<-unique(input) + } else { + stop(paste(id_type,"not found in your ids list, please check your IDs in input or the selected column of your input file")) } ontology <- strsplit(args$onto_opt, ",")[[1]] + ## Extract GGO/EGO arguments - if (args$go_represent == "true") { - go_represent <- args$go_represent - level <- as.numeric(args$level) - } - if (args$go_enrich == "true") { - go_enrich <- args$go_enrich + if (go_represent) {level <- as.numeric(args$level)} + if (go_enrich) { pval_cutoff <- as.numeric(args$pval_cutoff) qval_cutoff <- as.numeric(args$qval_cutoff) # Extract universe background genes (same as input file) @@ -164,52 +219,59 @@ universe_type = args$universe_type if (universe_type == "text") { universe = strsplit(args$universe, "[ \t\n]+")[[1]] - } - else if (universe_type == "file") { + } else if (universe_type == "file") { universe_filename = args$universe universe_ncol = args$uncol # Check ncol if (! as.numeric(gsub("c", "", universe_ncol)) %% 1 == 0) { stop("Please enter the right format for column number: c[number]") - } - else { + } else { universe_ncol = as.numeric(gsub("c", "", universe_ncol)) } - universe_header = args$uheader + universe_header = str2bool(args$uheader) # Get file content - universe_file = readfile(universe_filename, universe_header) + universe_file = read_file(universe_filename, universe_header) # Extract Protein IDs list - universe = c() - for (row in as.character(universe_file[,universe_ncol])) { - universe = c(universe, strsplit(row, ";")[[1]][1]) - } + universe <- sapply(universe_file[,universe_ncol], function(x) rapply(strsplit(x,";"),c),USE.NAMES = FALSE) } universe_id_type = args$universe_id_type ##to initialize - if (universe_id_type=="Uniprot") { + if (universe_id_type=="Uniprot" & any(check_ids(universe,"uniprot"))) { idFrom<-"UNIPROT" idTo<-"ENTREZID" - universe_gene<-bitr(universe, fromType=idFrom, toType=idTo, OrgDb=orgdb) + suppressMessages(universe_gene<-bitr(universe, fromType=idFrom, toType=idTo, OrgDb=orgdb)) universe_gene<-unique(universe_gene$ENTREZID) - } - else if (universe_id_type=="Entrez") { - universe_gene<-unique(universe) - } - } - else { + } else if (universe_id_type=="Entrez" & any(check_ids(universe,"entrez"))) { + universe_gene<-unique(unlist(universe)) + } else { + if (universe_type=="text"){ + print(paste(universe_id_type,"not found in your background IDs list",sep=" ")) + } else { + print(paste(universe_id_type,"not found in the column",universe_ncol,"of your background IDs file",sep=" ")) + } + universe_gene = NULL + } + } else { universe_gene = NULL } + } else { + universe_gene = NULL } ##enrichGO : GO over-representation test for (onto in ontology) { - if (args$go_represent == "true") { + if (go_represent) { ggo<-repartition.GO(gene, orgdb, onto, level, readable=TRUE) - write.table(ggo, args$text_output, append = TRUE, sep="\t", row.names = FALSE, quote=FALSE) + if (is.list(ggo)){ggo <- as.data.frame(apply(ggo, c(1,2), function(x) gsub("^$|^ $", NA, x)))} #convert "" and " " to NA + output_path = paste("cluster_profiler_GGO_",onto,".tsv",sep="") + write.table(ggo, output_path, sep="\t", row.names = FALSE, quote = FALSE ) } - if (args$go_enrich == "true") { - ego<-enrich.GO(gene, universe_gene, orgdb, onto, pval_cutoff, qval_cutoff) - write.table(ego, args$text_output, append = TRUE, sep="\t", row.names = FALSE, quote=FALSE) + + if (go_enrich) { + ego<-enrich.GO(gene, universe_gene, orgdb, onto, pval_cutoff, qval_cutoff,plot) + if (is.list(ego)){ego <- as.data.frame(apply(ego, c(1,2), function(x) gsub("^$|^ $", NA, x)))} #convert "" and " " to NA + output_path = paste("cluster_profiler_EGO_",onto,".tsv",sep="") + write.table(ego, output_path, sep="\t", row.names = FALSE, quote = FALSE ) } } }
--- a/README.rst Thu Mar 29 11:43:28 2018 -0400 +++ b/README.rst Tue Dec 18 09:21:32 2018 -0500 @@ -31,7 +31,7 @@ compared to a background (whole organism or user-defined list). **Input required** - + This component works with Gene ids (e.g : 4151, 7412) or Uniprot accession number (e.g. P31946). You can copy/paste these identifiers or supply a tabular file (.csv, .tsv, .txt, .tab) where there are contained. @@ -42,11 +42,4 @@ **User manual / Documentation** of the clusterProfiler R package (functions and parameters): https://bioconductor.org/packages/3.7/bioc/vignettes/clusterProfiler/inst/doc/clusterProfiler.html -(Very well explained) - -**Reference** - -clusterProfiler R package reference : -G Yu, LG Wang, Y Han, QY He. clusterProfiler: an R package for comparing biological themes among gene clusters. -OMICS: A Journal of Integrative Biology 2012, 16(5):284-287. -doi:[10.1089/omi.2011.0118](http://dx.doi.org/10.1089/omi.2011.0118) +(Very well explained) \ No newline at end of file
--- a/cluster_profiler.xml Thu Mar 29 11:43:28 2018 -0400 +++ b/cluster_profiler.xml Tue Dec 18 09:21:32 2018 -0500 @@ -1,11 +1,10 @@ -<tool id="cluter_profiler" name="clusterProfiler" version="0.1.0"> - <description> - GO terms classification and enrichment analysis - </description> +<tool id="cluter_profiler" name="GO terms classification and enrichment analysis" version="2018.12.18"> + <description>(Human, Mouse, Rat)[clusterProfiler]</description> <requirements> <requirement type="package" version="3.4.1">R</requirement> <requirement type="package" version="3.5.0">bioconductor-org.hs.eg.db</requirement> <requirement type="package" version="3.5.0">bioconductor-org.mm.eg.db</requirement> + <requirement type="package" version="3.5.0">bioconductor-org.Rn.eg.db</requirement> <requirement type="package" version="3.2.0">bioconductor-dose</requirement> <requirement type="package" version="3.4.4">bioconductor-clusterprofiler</requirement> </requirements> @@ -37,30 +36,29 @@ --pval_cutoff="$ego.pval" --qval_cutoff="$ego.qval" #if $ego.universe.universe_option == "true" - #if $ego.universe.universe_input.universe_ids == "text" - --universe_type="text" - --universe="$ego.universe.universe_input.txt" - #else - --universe_type="file" - --universe="$ego.universe.universe_input.file" - --uncol="$ego.universe.universe_input.ncol" - --uheader="$ego.universe.universe_input.header" + #if $ego.universe.universe_input.universe_ids == "text" + --universe_type="text" + --universe="$ego.universe.universe_input.txt" + #else + --universe_type="file" + --universe="$ego.universe.universe_input.file" + --uncol="$ego.universe.universe_input.ncol" + --uheader="$ego.universe.universe_input.header" + #end if + --universe_id_type="$ego.universe.universe_idti.universe_idtypein" #end if - --universe_id_type="$ego.universe.universe_idti.universe_idtypein" - #end if #else --go_enrich="false" #end if - --onto_opt="$ontology" - - --text_output="$text_output" + --plot="$ego.plot" + --onto_opt="$ontology" > $log ]]></command> <inputs> <conditional name="input" > - <param name="ids" type="select" label="Provide your identifiers" help="Copy/paste or ID list from a file (e.g. table)" > - <option value="text">Copy/paste your identifiers</option> - <option value="file" selected="true">Input file containing your identifiers</option> + <param name="ids" type="select" label="Enter your IDs (UniProt Accession numer or Gene ID)" help="Copy/paste or from a file (e.g. table)" > + <option value="text">Copy/paste your IDs</option> + <option value="file" selected="true">Input file containing your IDs</option> </param> <when value="text" > <param name="txt" type="text" label="Copy/paste your identifiers" help='IDs must be separated by spaces into the form field, for example: P31946 P62258' > @@ -76,50 +74,54 @@ </when> <when value="file" > <param name="file" type="data" format="txt,tabular" label="Choose a file that contains your list of IDs" help="" /> - <param name="header" type="boolean" checked="true" truevalue="true" falsevalue="false" label="Does your input file contain header?" /> - <param name="ncol" type="text" value="c1" label="The column number of IDs to map" help='For example, fill in "c1" if it is the first column, "c2" if it is the second column and so on' /> + <param name="header" type="boolean" checked="true" truevalue="true" falsevalue="false" label="Does file contain header?" /> + <param name="ncol" type="text" value="c1" label="Column number of IDs" help='For example, fill in "c1" if it is the first column, "c2" if it is the second column and so on' /> </when> </conditional> <conditional name="idti" > - <param name="idtypein" type="select" label="Select type/source of identifier of your list" help="Please see example of IDs in help section" > - <option value="Uniprot">UniProt accession number</option> - <option value="Entrez">Entrez Gene ID</option> + <param name="idtypein" type="select" label="Select type/source of IDs" help="" > + <option value="Uniprot">UniProt accession number (e.g.:P31946)</option> + <option value="Entrez">Entrez Gene ID (e.g.:4151)</option> </param> <when value="Uniprot"/> <when value="Entrez"/> - </conditional> - - <param name="species" type="select" label="Select a species" > - <option value="human">Human</option> - <option value="mouse">Mouse</option> - <option value="rat">Rat</option> + </conditional> + <param name="species" type="select" label="Species" > + <option value="org.Hs.eg.db">Human (Homo sapiens) </option> + <option value="org.Mm.eg.db">Mouse (Mus musculus) </option> + <option value="org.Rn.eg.db">Rat (Rattus norvegicus)</option> + </param> + <param name="ontology" type="select" display="checkboxes" multiple="true" label="Select GO terms category" optional="false" > + <option value="CC">Cellular Component</option> + <option value="BP">Biological Process</option> + <option value="MF">Molecular Function</option> </param> <conditional name="ggo"> - <param name="go_represent" type="boolean" checked="true" truevalue="true" falsevalue="false" label="Do you want to perform GO categories representation analysis?"/> + <param name="go_represent" type="boolean" checked="true" truevalue="true" falsevalue="false" label="Perform GO categories representation analysis?"/> <when value="true"> - <param name="level" type="select" label="Level of the ontology at which the profile has to be built (the higher this number, the deeper the GO level)"> + <param name="level" type="select" label="Ontology level (the higher this number, the deeper the GO level)"> <option value="1">1</option> - <option value="2">2</option> - <option value="3" selected="True">3</option> + <option value="2" selected="True">2</option> + <option value="3">3</option> </param> </when> <when value="false"/> </conditional> <conditional name="ego"> - <param name="go_enrich" type="boolean" checked="true" truevalue="true" falsevalue="false" label="Do you want to perform GO categories enrichment analysis?"/> + <param name="go_enrich" type="boolean" checked="true" truevalue="true" falsevalue="false" label="Perform GO categories enrichment analysis?"/> <when value="true"> <param name="pval" type="float" value="0.01" label="P-value cut off"/> <param name="qval" type="float" value="0.05" label="Q-value cut off"/> <conditional name="universe" > - <param name="universe_option" type="boolean" checked="false" truevalue="true" falsevalue="false" label="Would you like to define your own background IDs?"/> + <param name="universe_option" type="boolean" checked="false" truevalue="true" falsevalue="false" label="Define your own background IDs?"/> <when value="true"> <conditional name="universe_input"> - <param name="universe_ids" type="select" label="Provide your background IDs list" help="Copy/paste or ID list from a file (e.g. table)" > - <option value="text">Copy/paste your background identifiers</option> - <option value="file" selected="true">Input file containing your background identifiers</option> + <param name="universe_ids" type="select" label="Enter your background IDs (UniProt Accession number or Entrez Gene ID)" help="Copy/paste or from a file (e.g. table)" > + <option value="text">Copy/paste your background IDs</option> + <option value="file" selected="true">Input file containing your background IDs</option> </param> <when value="text" > - <param name="txt" type="text" label="Copy/paste your background identifiers" help='IDs must be separated by spaces into the form field, for example: P31946 P62258' > + <param name="txt" type="text" label="Copy/paste your background IDs" help='IDs must be separated by spaces into the form field, for example: P31946 P62258' > <sanitizer> <valid initial="string.printable"> <remove value="'"/> @@ -131,14 +133,14 @@ </param> </when> <when value="file" > - <param name="file" type="data" format="txt,tabular" label="Choose a file that contains your background IDs list" help="" /> - <param name="header" type="boolean" checked="true" truevalue="true" falsevalue="false" label="Does your input file contain header?" /> - <param name="ncol" type="text" value="c1" label="The column number of IDs to map" help='For example, fill in "c1" if it is the first column, "c2" if it is the second column and so on' /> + <param name="file" type="data" format="txt,tabular" label="Select file that contains your background IDs list" help="" /> + <param name="header" type="boolean" checked="true" truevalue="true" falsevalue="false" label="Does file contain header?" /> + <param name="ncol" type="text" value="c1" label="Column number of IDs" help='For example, fill in "c1" if it is the first column, "c2" if it is the second column and so on' /> </when> </conditional> <conditional name="universe_idti" > - <param name="universe_idtypein" type="select" label="Select type/source of background identifier of your list" help="Please see example of IDs in help section" > - <option value="Uniprot">UniProt accession number</option> + <param name="universe_idtypein" type="select" label="Select type of background IDs" help="" > + <option value="Uniprot">UniProt Accession number</option> <option value="Entrez">Entrez Gene ID</option> </param> <when value="Uniprot"/> @@ -147,24 +149,22 @@ </when> <when value="false"/> </conditional> + <param name="plot" type="select" display="checkboxes" multiple="true" label="Graphical display" optional="false"> + <option selected = "true" value="dotplot">dot-plot</option> + <option value="barplot">bar-plot</option> + </param> </when> <when value="false"/> </conditional> - - <param name="ontology" type="select" display="checkboxes" multiple="true" label="Please select GO terms category"> - <option value="CC">Cellular Component</option> - <option value="BP">Biological Process</option> - <option value="MF">Molecular Function</option> - </param> - - - </inputs> <outputs> - <data name="text_output" format="tabular" label="clusterProfiler text output" /> - <collection type="list" label="clusterProfiler diagram outputs" name="output" > - <discover_datasets pattern="(?P<designation>.+\.png)" ext="png" /> - </collection> + <data name="log" format="tsv" label="Cluster profiler" /> + <collection type="list" label="clusterProfiler text files" name="text_output"> + <discover_datasets pattern="(?P<designation>.+\.tsv)" ext="tsv"/> + </collection> + <collection type="list" label="clusterProfiler diagram outputs" name="graph_output" > + <discover_datasets pattern="(?P<designation>.+plot)" ext="png" /> + </collection> </outputs> <tests> <test> @@ -177,53 +177,102 @@ <conditional name="idti"> <param name="idtypein" value="Uniprot"/> </conditional> - <param name="species" value="human"/> + <param name="species" value="org.Hs.eg.db"/> <conditional name="ggo"> <param name="go_represent" value="true"/> <param name="level" value="3"/> </conditional> <conditional name="ego"> - <param name="go_enrich" value="false"/> + <param name="go_enrich" value="true"/> + <conditional name="universe_input"> + <param name="universe_ids" value="file"/> + <param name="file" value="background_ids.txt"/> + <param name="header" value="true"/> + <param name="ncol" value="c7"/> + </conditional> + <conditional name="universe_idti" > + <param name="universe_idtypein" value="Uniprot"/> + </conditional> </conditional> - <param name="ontology" value="CC"/> - <output name="text_output" file="clusterProfiler_text_output.tabular"/> - <output_collection name="output"> - <element name="clusterProfiler_diagram_outputs__GGO.CC.png" file="clusterProfiler_diagram_outputs__GGO.CC.png" ftype="png"/> + <param name="ontology" value="CC,BP,MF"/> + <param name="plot" value="dotplot,barplot"/> + <output name="log" file="log.txt" /> + <output_collection name="text_output"> + <element name="cluster_profiler_GGO_CC.csv" file="cluster_profiler_GGO_CC.csv" ftype="csv"/> + <element name="cluster_profiler_EGO_BP.csv" file="cluster_profiler_GGO_BP.csv" ftype="csv"/> + <element name="cluster_profiler_GGO_MF.csv" file="cluster_profiler_GGO_MF.csv" ftype="csv"/> + <element name="cluster_profiler_EGO_CC.csv" file="cluster_profiler_EGO_CC.csv" ftype="csv"/> + <element name="cluster_profiler_EGO_BP.csv" file="cluster_profiler_EGO_BP.csv" ftype="csv"/> + <element name="cluster_profiler_EGO_MF.csv" file="cluster_profiler_EGO_MF.csv" ftype="csv"/> + </output_collection> + <output_collection name="graph_output"> + <element name="GGO_CC_bar-plot" file="GGO_CC_bar-plot" ftype="png"/> + <element name="GGO_BP_bar-plot" file="GGO_BP_bar-plot" ftype="png"/> + <element name="GGO_MF_bar-plot" file="GGO_MF_bar-plot" ftype="png"/> + <element name="EGO_CC_bar-plot" file="EGO_CC_bar-plot" ftype="png"/> + <element name="EGO_BP_bar-plot" file="EGO_BP_bar-plot" ftype="png"/> + <element name="EGO_CC_dot-plot" file="EGO_CC_dot-plot" ftype="png"/> + <element name="EGO_BP_dot-plot" file="EGO_BP_dot-plot" ftype="png"/> </output_collection> </test> </tests> <help><![CDATA[ - -**Galaxy component based on R package clusterProfiler (see ref below)** - -This component allows to perform GO enrichment-analyses. + +**Description** + +This tool is based on R package clusterProfiler and allows to perform GO terms classification and enrichment analyses on gene/protein sets (e.g. given a set of genes that are up-regulated under certain conditions, an enrichment analysis will find which GO terms are over-represented (or under-represented) using annotations for that gene/protein set). + +Given a list of IDs, this tool: -Given a list of IDs, the tool either - (i) performs gene classification based on GO distribution at a specific level, or - (ii) calculates GO categories enrichment (over- or under-representation) for the IDs of the input list, compared to a background (whole organism or user-defined list). +(i) performs gene classification based on GO distribution at a specific level, + +(ii) calculates GO categories enrichment (over- or under-representation) for the IDs of the input list, compared to a background. User has the possibility to use background corresponding to the whole organism or to a user-defined list. In this latter case, we recommand to use the "Build tissue-specific expression dataset" ProteoRE tool to create this list according to your need. + +----- + +**Input** + +Two modes are allowed: either by supplying a tabular file (.csv, .tsv, .txt, .tab) including your IDs (identifiers) or by copy/pasting your IDs (separated by a space). + +"Select type/source of IDs": only entrez gene ID (e.g : 4151, 7412) or Uniprot accession number (e.g. P31946) are allowed. If your list is not in this form, please use the ID_Converter tool of ProteoRE. + +----- -**Input required** +**Parameters** + +"Species": the three supported species are Homo sapiens, Mus musculus and Rattus norvegicus -This component works with Gene ids (e.g : 4151, 7412) or Uniprot accession number (e.g. P31946). +"Perform GO categories representation analysis?": classify genes based on their projection at a specific level of the GO corpus (see parameter below), and provides functions (set to "Yes") + +"Ontology level (the higher this number, the deeper the GO level)": correspond to the level of GO hierarchy (from 1 to 3) (set to level "2" by default). In general the higher the level, the more semantically specific the term is. + +"Perform GO categories enrichment analysis?": calculate enrichment test for GO terms based on hypergeometric distribution (set to "Yes") -Two modes are allowed: either by supplying a tabular file (.csv, .tsv, .txt, .tab) including your IDs (identifiers) -or by copy/pasting your IDs (separated by a space). +"P-value cut off": P-value threshold value for the declaration of significance (default is < 0.01) + +"Q-value cut off": to prevent high false discovery rate (FDR) in multiple testing, Q-values (adjusted P-values) are estimated for FDR control. (default is < 0.05) + +"Define your own background IDs?": by default the whole genome/proteome is used as a reference background to compute the enrichment. As this reference set should normally only include genes/proteins that were monitored during your analysis, this option allows to provide your own background; this could be for instance, the total number of genes/proteins expressed in the tissue/sample under study. - +If you want to use your own background, click on the "Yes" button. Your gene/protein set must be a list of Entrez gene ID or Uniprot accession number (otherwise, use the ID-Converter tool of ProteoRE). Select the file containing your list of ID (as background), then specify the column number which contains IDs and the type of IDs (gene Entrez or Uniprot Accession number) as requested. + +Of note: for Human species, you can build your own background by using the "Build tissue-specific expression dataset" tool of ProteoRE. + +----- + **Output** -Text (tables) and graphics representing the repartition and/or enrichment of GO categories. +Diagram output: graphical output in the form of bar-plot or dot-plot (png, jpeg or pdf format), one figure for each GO category. +Text tables: with the following information GO category description (e.g.BP.Description), GO term identifier (e.g. BP.GOID) and GO term frequency (e.g. BP.Frequency)d graphics representing the repartition and/or enrichment of GO categories. One table and one graphic will be produced for each GO catagory. -**User manual / Documentation** of the clusterProfiler R package (functions and parameters): -https://bioconductor.org/packages/3.7/bioc/vignettes/clusterProfiler/inst/doc/clusterProfiler.html -(Very well explained) +----- -**Reference** - -clusterProfiler R package reference : +**Authors** G Yu, LG Wang, Y Han, QY He. clusterProfiler: an R package for comparing biological themes among gene clusters. -OMICS: A Journal of Integrative Biology 2012, 16(5):284-287. -doi:[10.1089/omi.2011.0118](http://dx.doi.org/10.1089/omi.2011.0118) +OMICS: A Journal of Integrative Biology 2012, 16(5):284-287. doi:[10.1089/omi.2011.0118](http://dx.doi.org/10.1089/omi.2011.0118) + +User manual / Documentation of the clusterProfiler R package (functions and parameters): +https://bioconductor.org/packages/3.7/bioc/vignettes/clusterProfiler/inst/doc/clusterProfiler.html ----- @@ -231,9 +280,9 @@ **Galaxy integration** -T.P. Lien Nguyen, Florence Combes, Yves Vandenbrouck CEA, INSERM, CNRS, Grenoble-Alpes University, BIG Institute, FR +T.P. Lien Nguyen, Florence Combes, Yves Vandenbrouck - CEA, INSERM, CNRS, Grenoble-Alpes University, BIG Institute, FR -Sandra Dérozier, Olivier Rué, Christophe Caron, Valentin Loux INRA, Paris-Saclay University, MAIAGE Unit, Migale Bioinformatics platform +Sandra Dérozier, Olivier Rué, Christophe Caron, Valentin Loux - INRA, Paris-Saclay University, MAIAGE Unit, Migale Bioinformatics platform, FR This work has been partially funded through the French National Agency for Research (ANR) IFB project.
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/background_ids.txt Tue Dec 18 09:21:32 2018 -0500 @@ -0,0 +1,7380 @@ +Gene Gene.name Tissue Cell.type Level Reliability UniProt.AC GeneID +ENSG00000000938 FGR lung macrophages Medium Enhanced P09769 2268 +ENSG00000001167 NFYA bronchus respiratory epithelial cells Medium Enhanced P23511 4800 +ENSG00000001167 NFYA lung macrophages Low Enhanced P23511 4800 +ENSG00000001167 NFYA lung pneumocytes Medium Enhanced P23511 4800 +ENSG00000001497 LAS1L bronchus respiratory epithelial cells High Supported Q9Y4W2 81887 +ENSG00000001497 LAS1L lung pneumocytes Medium Supported Q9Y4W2 81887 +ENSG00000002549 LAP3 bronchus respiratory epithelial cells Medium Enhanced P28838 51056 +ENSG00000002549 LAP3 lung macrophages Medium Enhanced P28838 51056 +ENSG00000002549 LAP3 lung pneumocytes Low Enhanced P28838 51056 +ENSG00000002586 CD99 bronchus respiratory epithelial cells Medium Supported P14209 4267 +ENSG00000002586 CD99 lung macrophages Low Supported P14209 4267 +ENSG00000002822 MAD1L1 bronchus respiratory epithelial cells Medium Supported Q9Y6D9 8379 +ENSG00000002822 MAD1L1 lung macrophages Medium Supported Q9Y6D9 8379 +ENSG00000002822 MAD1L1 lung pneumocytes Low Supported Q9Y6D9 8379 +ENSG00000002834 LASP1 bronchus respiratory epithelial cells Low Enhanced Q14847 3927 +ENSG00000002834 LASP1 lung macrophages Medium Enhanced Q14847 3927 +ENSG00000002834 LASP1 lung pneumocytes Low Enhanced Q14847 3927 +ENSG00000003436 TFPI bronchus respiratory epithelial cells Medium Supported P10646 7035 +ENSG00000003436 TFPI lung macrophages High Supported P10646 7035 +ENSG00000003436 TFPI lung pneumocytes Medium Supported P10646 7035 +ENSG00000004478 FKBP4 bronchus respiratory epithelial cells Low Enhanced Q02790 2288 +ENSG00000004478 FKBP4 lung macrophages Low Enhanced Q02790 2288 +ENSG00000004487 KDM1A bronchus respiratory epithelial cells High Supported O60341 23028 +ENSG00000004487 KDM1A lung macrophages Medium Supported O60341 23028 +ENSG00000004487 KDM1A lung pneumocytes High Supported O60341 23028 +ENSG00000004534 RBM6 bronchus respiratory epithelial cells High Enhanced P78332 10180 +ENSG00000004534 RBM6 lung macrophages High Enhanced P78332 10180 +ENSG00000004534 RBM6 lung pneumocytes High Enhanced P78332 10180 +ENSG00000004700 RECQL bronchus respiratory epithelial cells Medium Enhanced P46063 5965 +ENSG00000004700 RECQL lung macrophages Low Enhanced P46063 5965 +ENSG00000004700 RECQL lung pneumocytes Low Enhanced P46063 5965 +ENSG00000004777 ARHGAP33 bronchus respiratory epithelial cells Low Supported O14559 115703 +ENSG00000004777 ARHGAP33 lung macrophages Low Supported O14559 115703 +ENSG00000004777 ARHGAP33 lung pneumocytes Medium Supported O14559 115703 +ENSG00000004897 CDC27 bronchus respiratory epithelial cells High Supported P30260 996 +ENSG00000004897 CDC27 lung macrophages Low Supported P30260 996 +ENSG00000004897 CDC27 lung pneumocytes Medium Supported P30260 996 +ENSG00000005020 SKAP2 lung macrophages Medium Enhanced O75563 8935 +ENSG00000005059 MCUB bronchus respiratory epithelial cells Low Enhanced Q9NWR8 55013 +ENSG00000005108 THSD7A lung macrophages Low Supported Q9UPZ6 221981 +ENSG00000005156 LIG3 bronchus respiratory epithelial cells High Supported P49916 3980 +ENSG00000005156 LIG3 lung macrophages Medium Supported P49916 3980 +ENSG00000005156 LIG3 lung pneumocytes Medium Supported P49916 3980 +ENSG00000005175 RPAP3 bronchus respiratory epithelial cells High Enhanced Q9H6T3 79657 +ENSG00000005175 RPAP3 lung macrophages Medium Enhanced Q9H6T3 79657 +ENSG00000005175 RPAP3 lung pneumocytes Medium Enhanced Q9H6T3 79657 +ENSG00000005189 AC004381.6 bronchus respiratory epithelial cells Medium Enhanced Q96IC2 81691 +ENSG00000005189 AC004381.6 lung macrophages Medium Enhanced Q96IC2 81691 +ENSG00000005194 CIAPIN1 bronchus respiratory epithelial cells Low Enhanced Q6FI81 57019 +ENSG00000005249 PRKAR2B bronchus respiratory epithelial cells Low Enhanced NA NA +ENSG00000005249 PRKAR2B lung macrophages Low Enhanced NA NA +ENSG00000005339 CREBBP bronchus respiratory epithelial cells Medium Enhanced Q92793 1387 +ENSG00000005339 CREBBP lung macrophages Medium Enhanced Q92793 1387 +ENSG00000005339 CREBBP lung pneumocytes Medium Enhanced Q92793 1387 +ENSG00000005379 TSPOAP1 bronchus respiratory epithelial cells Medium Enhanced O95153 9256 +ENSG00000005379 TSPOAP1 lung macrophages Low Enhanced O95153 9256 +ENSG00000005448 WDR54 bronchus respiratory epithelial cells High Enhanced Q9H977 84058 +ENSG00000005448 WDR54 lung macrophages High Enhanced Q9H977 84058 +ENSG00000005469 CROT bronchus respiratory epithelial cells Medium Enhanced Q9UKG9 54677 +ENSG00000005469 CROT lung macrophages Medium Enhanced Q9UKG9 54677 +ENSG00000005882 PDK2 bronchus respiratory epithelial cells High Supported Q15119 5164 +ENSG00000005882 PDK2 lung macrophages Medium Supported Q15119 5164 +ENSG00000005882 PDK2 lung pneumocytes Low Supported Q15119 5164 +ENSG00000005884 ITGA3 bronchus respiratory epithelial cells Medium Enhanced P26006 3675 +ENSG00000005884 ITGA3 lung macrophages Medium Enhanced P26006 3675 +ENSG00000005884 ITGA3 lung pneumocytes Medium Enhanced P26006 3675 +ENSG00000005889 ZFX bronchus respiratory epithelial cells Low Supported P17010 7543 +ENSG00000005889 ZFX lung macrophages Low Supported P17010 7543 +ENSG00000005889 ZFX lung pneumocytes Low Supported P17010 7543 +ENSG00000005893 LAMP2 bronchus respiratory epithelial cells Medium Enhanced P13473 3920 +ENSG00000005893 LAMP2 lung macrophages High Enhanced P13473 3920 +ENSG00000005893 LAMP2 lung pneumocytes Medium Enhanced P13473 3920 +ENSG00000006118 TMEM132A bronchus respiratory epithelial cells Medium Enhanced Q24JP5 54972 +ENSG00000006282 SPATA20 bronchus respiratory epithelial cells Low Enhanced Q8TB22 64847 +ENSG00000006453 BAIAP2L1 bronchus respiratory epithelial cells Medium Enhanced Q9UHR4 55971 +ENSG00000006453 BAIAP2L1 lung macrophages Low Enhanced Q9UHR4 55971 +ENSG00000006453 BAIAP2L1 lung pneumocytes Low Enhanced Q9UHR4 55971 +ENSG00000006530 AGK bronchus respiratory epithelial cells High Supported E9PG39 NA +ENSG00000006530 AGK lung macrophages Medium Supported E9PG39 NA +ENSG00000006530 AGK lung pneumocytes Low Supported E9PG39 NA +ENSG00000006611 USH1C bronchus respiratory epithelial cells Low Supported Q9Y6N9 10083 +ENSG00000006611 USH1C lung macrophages Low Supported Q9Y6N9 10083 +ENSG00000006695 COX10 bronchus respiratory epithelial cells Medium Supported Q12887 1352 +ENSG00000006695 COX10 lung macrophages Medium Supported Q12887 1352 +ENSG00000006695 COX10 lung pneumocytes Medium Supported Q12887 1352 +ENSG00000007062 PROM1 bronchus respiratory epithelial cells Medium Enhanced O43490 8842 +ENSG00000007062 PROM1 lung macrophages Low Enhanced O43490 8842 +ENSG00000007080 CCDC124 bronchus respiratory epithelial cells High Supported Q96CT7 115098 +ENSG00000007080 CCDC124 lung macrophages Medium Supported Q96CT7 115098 +ENSG00000007080 CCDC124 lung pneumocytes Medium Supported Q96CT7 115098 +ENSG00000007174 DNAH9 bronchus respiratory epithelial cells High Enhanced Q9NYC9 1770 +ENSG00000007372 PAX6 bronchus respiratory epithelial cells Medium Supported P26367 5080 +ENSG00000007392 LUC7L bronchus respiratory epithelial cells High Supported Q9NQ29 55692 +ENSG00000007392 LUC7L lung macrophages High Supported Q9NQ29 55692 +ENSG00000007392 LUC7L lung pneumocytes High Supported Q9NQ29 55692 +ENSG00000007402 CACNA2D2 lung macrophages Low Enhanced Q9NY47 9254 +ENSG00000007402 CACNA2D2 lung pneumocytes Medium Enhanced Q9NY47 9254 +ENSG00000007933 FMO3 bronchus respiratory epithelial cells Low Enhanced P31513 2328 +ENSG00000008018 PSMB1 bronchus respiratory epithelial cells High Enhanced P20618 5689 +ENSG00000008018 PSMB1 lung macrophages Medium Enhanced P20618 5689 +ENSG00000008018 PSMB1 lung pneumocytes Medium Enhanced P20618 5689 +ENSG00000008086 CDKL5 bronchus respiratory epithelial cells Medium Supported O76039 6792 +ENSG00000008086 CDKL5 lung macrophages Low Supported O76039 6792 +ENSG00000008086 CDKL5 lung pneumocytes Low Supported O76039 6792 +ENSG00000008128 CDK11A lung macrophages Medium Enhanced Q9UQ88 728642 +ENSG00000008128 CDK11A lung pneumocytes Medium Enhanced Q9UQ88 728642 +ENSG00000008196 TFAP2B bronchus respiratory epithelial cells Medium Supported Q92481 7021 +ENSG00000008196 TFAP2B lung macrophages Low Supported Q92481 7021 +ENSG00000008311 AASS bronchus respiratory epithelial cells Medium Enhanced Q9UDR5 10157 +ENSG00000008311 AASS lung macrophages Low Enhanced Q9UDR5 10157 +ENSG00000008311 AASS lung pneumocytes Medium Enhanced Q9UDR5 10157 +ENSG00000008394 MGST1 bronchus respiratory epithelial cells Low Enhanced P10620 4257 +ENSG00000008394 MGST1 lung macrophages Low Enhanced P10620 4257 +ENSG00000008394 MGST1 lung pneumocytes Medium Enhanced P10620 4257 +ENSG00000008438 PGLYRP1 lung macrophages Low Enhanced O75594 8993 +ENSG00000008441 NFIX bronchus respiratory epithelial cells High Supported Q14938 4784 +ENSG00000008441 NFIX lung macrophages Low Supported Q14938 4784 +ENSG00000008441 NFIX lung pneumocytes Low Supported Q14938 4784 +ENSG00000009307 CSDE1 bronchus respiratory epithelial cells Medium Enhanced O75534 7812 +ENSG00000009307 CSDE1 lung macrophages Low Enhanced O75534 7812 +ENSG00000009307 CSDE1 lung pneumocytes Low Enhanced O75534 7812 +ENSG00000009790 TRAF3IP3 lung macrophages Low Enhanced Q9Y228 80342 +ENSG00000009954 BAZ1B bronchus respiratory epithelial cells Medium Supported Q9UIG0 9031 +ENSG00000009954 BAZ1B lung macrophages Low Supported Q9UIG0 9031 +ENSG00000009954 BAZ1B lung pneumocytes Medium Supported Q9UIG0 9031 +ENSG00000010244 ZNF207 bronchus respiratory epithelial cells High Enhanced O43670 7756 +ENSG00000010244 ZNF207 lung macrophages High Enhanced O43670 7756 +ENSG00000010244 ZNF207 lung pneumocytes High Enhanced O43670 7756 +ENSG00000010256 UQCRC1 bronchus respiratory epithelial cells High Enhanced P31930 7384 +ENSG00000010256 UQCRC1 lung macrophages High Enhanced P31930 7384 +ENSG00000010256 UQCRC1 lung pneumocytes High Enhanced P31930 7384 +ENSG00000010270 STARD3NL bronchus respiratory epithelial cells Medium Enhanced O95772 83930 +ENSG00000010270 STARD3NL lung macrophages Medium Enhanced O95772 83930 +ENSG00000010270 STARD3NL lung pneumocytes Medium Enhanced O95772 83930 +ENSG00000010278 CD9 bronchus respiratory epithelial cells Medium Supported P21926 928 +ENSG00000010278 CD9 lung macrophages High Supported P21926 928 +ENSG00000010278 CD9 lung pneumocytes High Supported P21926 928 +ENSG00000010292 NCAPD2 bronchus respiratory epithelial cells Medium Supported Q15021 9918 +ENSG00000010292 NCAPD2 lung macrophages Medium Supported Q15021 9918 +ENSG00000010292 NCAPD2 lung pneumocytes Low Supported Q15021 9918 +ENSG00000010626 LRRC23 bronchus respiratory epithelial cells High Enhanced Q53EV4 10233 +ENSG00000010671 BTK lung macrophages Medium Enhanced Q06187 695 +ENSG00000011028 MRC2 bronchus respiratory epithelial cells Low Enhanced Q9UBG0 9902 +ENSG00000011028 MRC2 lung macrophages Medium Enhanced Q9UBG0 9902 +ENSG00000011028 MRC2 lung pneumocytes Low Enhanced Q9UBG0 9902 +ENSG00000011143 MKS1 bronchus respiratory epithelial cells High Enhanced Q9NXB0 54903 +ENSG00000011143 MKS1 lung pneumocytes Medium Enhanced Q9NXB0 54903 +ENSG00000011243 AKAP8L bronchus respiratory epithelial cells High Enhanced Q9ULX6 26993 +ENSG00000011243 AKAP8L lung macrophages Medium Enhanced Q9ULX6 26993 +ENSG00000011243 AKAP8L lung pneumocytes Medium Enhanced Q9ULX6 26993 +ENSG00000011275 RNF216 bronchus respiratory epithelial cells Medium Supported Q9NWF9 54476 +ENSG00000011275 RNF216 lung macrophages Medium Supported Q9NWF9 54476 +ENSG00000011275 RNF216 lung pneumocytes Medium Supported Q9NWF9 54476 +ENSG00000011295 TTC19 bronchus respiratory epithelial cells Medium Enhanced Q6DKK2 54902 +ENSG00000011295 TTC19 lung macrophages Low Enhanced Q6DKK2 54902 +ENSG00000011295 TTC19 lung pneumocytes Low Enhanced Q6DKK2 54902 +ENSG00000011304 PTBP1 bronchus respiratory epithelial cells High Supported P26599 5725 +ENSG00000011304 PTBP1 lung macrophages High Supported P26599 5725 +ENSG00000011304 PTBP1 lung pneumocytes High Supported P26599 5725 +ENSG00000011426 ANLN bronchus respiratory epithelial cells Medium Enhanced Q9NQW6 54443 +ENSG00000011426 ANLN lung macrophages Low Enhanced Q9NQW6 54443 +ENSG00000011426 ANLN lung pneumocytes Low Enhanced Q9NQW6 54443 +ENSG00000011451 WIZ bronchus respiratory epithelial cells High Supported O95785 58525 +ENSG00000011451 WIZ lung macrophages Medium Supported O95785 58525 +ENSG00000011451 WIZ lung pneumocytes High Supported O95785 58525 +ENSG00000011454 RABGAP1 bronchus respiratory epithelial cells High Enhanced Q9Y3P9 23637 +ENSG00000011454 RABGAP1 lung macrophages Low Enhanced Q9Y3P9 23637 +ENSG00000011454 RABGAP1 lung pneumocytes Low Enhanced Q9Y3P9 23637 +ENSG00000011465 DCN bronchus respiratory epithelial cells Medium Enhanced P07585 1634 +ENSG00000011523 CEP68 bronchus respiratory epithelial cells Medium Enhanced Q76N32 23177 +ENSG00000011523 CEP68 lung macrophages Medium Enhanced Q76N32 23177 +ENSG00000011523 CEP68 lung pneumocytes Medium Enhanced Q76N32 23177 +ENSG00000011590 ZBTB32 lung macrophages Medium Enhanced Q9Y2Y4 27033 +ENSG00000011600 TYROBP lung macrophages High Enhanced O43914 7305 +ENSG00000012048 BRCA1 bronchus respiratory epithelial cells Medium Enhanced P38398 672 +ENSG00000012048 BRCA1 lung macrophages Medium Enhanced P38398 672 +ENSG00000012048 BRCA1 lung pneumocytes Medium Enhanced P38398 672 +ENSG00000012061 ERCC1 bronchus respiratory epithelial cells High Enhanced P07992 2067 +ENSG00000012061 ERCC1 lung macrophages Medium Enhanced P07992 2067 +ENSG00000012223 LTF bronchus respiratory epithelial cells Medium Enhanced P02788 4057 +ENSG00000012660 ELOVL5 bronchus respiratory epithelial cells Medium Enhanced Q9NYP7 60481 +ENSG00000012660 ELOVL5 lung macrophages Medium Enhanced Q9NYP7 60481 +ENSG00000012660 ELOVL5 lung pneumocytes Low Enhanced Q9NYP7 60481 +ENSG00000012779 ALOX5 lung macrophages High Enhanced NA NA +ENSG00000013364 MVP bronchus respiratory epithelial cells High Enhanced Q14764 9961 +ENSG00000013364 MVP lung macrophages High Enhanced Q14764 9961 +ENSG00000013503 POLR3B bronchus respiratory epithelial cells High Supported Q9NW08 55703 +ENSG00000013503 POLR3B lung macrophages High Supported Q9NW08 55703 +ENSG00000013503 POLR3B lung pneumocytes Medium Supported Q9NW08 55703 +ENSG00000013573 DDX11 bronchus respiratory epithelial cells Medium Supported Q96FC9 1663 +ENSG00000013573 DDX11 lung macrophages Low Supported Q96FC9 1663 +ENSG00000013573 DDX11 lung pneumocytes Medium Supported Q96FC9 1663 +ENSG00000013588 GPRC5A lung macrophages Medium Enhanced Q8NFJ5 9052 +ENSG00000013588 GPRC5A lung pneumocytes High Enhanced Q8NFJ5 9052 +ENSG00000013810 TACC3 lung macrophages Low Enhanced Q9Y6A5 10460 +ENSG00000014123 UFL1 bronchus respiratory epithelial cells Medium Enhanced O94874 23376 +ENSG00000014123 UFL1 lung macrophages Medium Enhanced O94874 23376 +ENSG00000014138 POLA2 bronchus respiratory epithelial cells Medium Enhanced Q14181 23649 +ENSG00000014138 POLA2 lung macrophages Medium Enhanced Q14181 23649 +ENSG00000014138 POLA2 lung pneumocytes Low Enhanced Q14181 23649 +ENSG00000014216 CAPN1 bronchus respiratory epithelial cells High Enhanced P07384 823 +ENSG00000014216 CAPN1 lung macrophages High Enhanced P07384 823 +ENSG00000014216 CAPN1 lung pneumocytes High Enhanced P07384 823 +ENSG00000015153 YAF2 bronchus respiratory epithelial cells High Enhanced Q8IY57 10138 +ENSG00000015153 YAF2 lung macrophages Medium Enhanced Q8IY57 10138 +ENSG00000015153 YAF2 lung pneumocytes Medium Enhanced Q8IY57 10138 +ENSG00000015285 WAS lung macrophages Medium Enhanced P42768 7454 +ENSG00000015475 BID lung macrophages Low Enhanced P55957 637 +ENSG00000015479 MATR3 bronchus respiratory epithelial cells High Enhanced P43243 9782 +ENSG00000015479 MATR3 lung macrophages Medium Enhanced P43243 9782 +ENSG00000015479 MATR3 lung pneumocytes High Enhanced P43243 9782 +ENSG00000015676 NUDCD3 bronchus respiratory epithelial cells Medium Enhanced Q8IVD9 23386 +ENSG00000015676 NUDCD3 lung macrophages Medium Enhanced Q8IVD9 23386 +ENSG00000015676 NUDCD3 lung pneumocytes Low Enhanced Q8IVD9 23386 +ENSG00000017260 ATP2C1 bronchus respiratory epithelial cells Medium Supported P98194 27032 +ENSG00000017260 ATP2C1 lung macrophages Medium Supported P98194 27032 +ENSG00000017260 ATP2C1 lung pneumocytes Medium Supported P98194 27032 +ENSG00000018189 RUFY3 bronchus respiratory epithelial cells Medium Enhanced Q7L099 22902 +ENSG00000018189 RUFY3 lung macrophages Medium Enhanced Q7L099 22902 +ENSG00000018189 RUFY3 lung pneumocytes Low Enhanced Q7L099 22902 +ENSG00000018408 WWTR1 bronchus respiratory epithelial cells Medium Enhanced Q9GZV5 25937 +ENSG00000018408 WWTR1 lung macrophages High Enhanced Q9GZV5 25937 +ENSG00000018408 WWTR1 lung pneumocytes High Enhanced Q9GZV5 25937 +ENSG00000018510 AGPS bronchus respiratory epithelial cells Medium Supported O00116 8540 +ENSG00000019102 VSIG2 bronchus respiratory epithelial cells Low Enhanced Q96IQ7 23584 +ENSG00000019169 MARCO lung macrophages High Enhanced Q9UEW3 8685 +ENSG00000019549 SNAI2 lung macrophages Medium Supported O43623 6591 +ENSG00000019549 SNAI2 lung pneumocytes High Supported O43623 6591 +ENSG00000019582 CD74 bronchus respiratory epithelial cells Medium Enhanced P04233 972 +ENSG00000019582 CD74 lung macrophages Medium Enhanced P04233 972 +ENSG00000020922 MRE11 bronchus respiratory epithelial cells High Supported P49959 4361 +ENSG00000020922 MRE11 lung macrophages High Supported P49959 4361 +ENSG00000020922 MRE11 lung pneumocytes High Supported P49959 4361 +ENSG00000021852 C8B lung macrophages Low Supported P07358 732 +ENSG00000022267 FHL1 lung pneumocytes Low Enhanced Q13642 2273 +ENSG00000023191 RNH1 bronchus respiratory epithelial cells Medium Enhanced E9PIK5 NA +ENSG00000023191 RNH1 lung macrophages Medium Enhanced E9PIK5 NA +ENSG00000023191 RNH1 lung pneumocytes Low Enhanced E9PIK5 NA +ENSG00000023318 ERP44 bronchus respiratory epithelial cells Medium Supported Q9BS26 23071 +ENSG00000023318 ERP44 lung macrophages Medium Supported Q9BS26 23071 +ENSG00000023318 ERP44 lung pneumocytes Medium Supported Q9BS26 23071 +ENSG00000023330 ALAS1 bronchus respiratory epithelial cells Medium Enhanced P13196 211 +ENSG00000023330 ALAS1 lung macrophages Medium Enhanced P13196 211 +ENSG00000023330 ALAS1 lung pneumocytes Medium Enhanced P13196 211 +ENSG00000023516 AKAP11 lung macrophages High Enhanced Q9UKA4 11215 +ENSG00000023516 AKAP11 lung pneumocytes Medium Enhanced Q9UKA4 11215 +ENSG00000023572 GLRX2 bronchus respiratory epithelial cells High Supported Q9NS18 51022 +ENSG00000023572 GLRX2 lung macrophages Low Supported Q9NS18 51022 +ENSG00000023572 GLRX2 lung pneumocytes High Supported Q9NS18 51022 +ENSG00000023839 ABCC2 bronchus respiratory epithelial cells Medium Enhanced Q92887 1244 +ENSG00000023839 ABCC2 lung macrophages Medium Enhanced Q92887 1244 +ENSG00000023892 DEF6 lung macrophages Low Enhanced Q9H4E7 50619 +ENSG00000025423 HSD17B6 lung pneumocytes Low Enhanced O14756 8630 +ENSG00000025708 TYMP lung macrophages Medium Enhanced P19971 1890 +ENSG00000025770 NCAPH2 bronchus respiratory epithelial cells Medium Enhanced Q6IBW4 29781 +ENSG00000025770 NCAPH2 lung macrophages Low Enhanced Q6IBW4 29781 +ENSG00000025770 NCAPH2 lung pneumocytes Low Enhanced Q6IBW4 29781 +ENSG00000025772 TOMM34 bronchus respiratory epithelial cells High Enhanced Q15785 10953 +ENSG00000025772 TOMM34 lung macrophages Medium Enhanced Q15785 10953 +ENSG00000025796 SEC63 bronchus respiratory epithelial cells Medium Enhanced Q9UGP8 11231 +ENSG00000025796 SEC63 lung macrophages Low Enhanced Q9UGP8 11231 +ENSG00000025796 SEC63 lung pneumocytes Low Enhanced Q9UGP8 11231 +ENSG00000025800 KPNA6 bronchus respiratory epithelial cells High Supported O60684 23633 +ENSG00000025800 KPNA6 lung macrophages High Supported O60684 23633 +ENSG00000025800 KPNA6 lung pneumocytes Medium Supported O60684 23633 +ENSG00000026025 VIM bronchus respiratory epithelial cells Low Enhanced P08670 7431 +ENSG00000026025 VIM lung macrophages High Enhanced P08670 7431 +ENSG00000026025 VIM lung pneumocytes High Enhanced P08670 7431 +ENSG00000026103 FAS bronchus respiratory epithelial cells Medium Enhanced P25445 355 +ENSG00000026103 FAS lung macrophages Low Enhanced P25445 355 +ENSG00000026508 CD44 bronchus respiratory epithelial cells High Enhanced P16070 960 +ENSG00000026508 CD44 lung macrophages Medium Enhanced P16070 960 +ENSG00000026508 CD44 lung pneumocytes Low Enhanced P16070 960 +ENSG00000026751 SLAMF7 lung macrophages Low Enhanced Q9NQ25 57823 +ENSG00000027847 B4GALT7 bronchus respiratory epithelial cells Low Supported Q9UBV7 11285 +ENSG00000027847 B4GALT7 lung pneumocytes Low Supported Q9UBV7 11285 +ENSG00000028839 TBPL1 bronchus respiratory epithelial cells Low Enhanced P62380 9519 +ENSG00000028839 TBPL1 lung macrophages Low Enhanced P62380 9519 +ENSG00000028839 TBPL1 lung pneumocytes Low Enhanced P62380 9519 +ENSG00000029363 BCLAF1 bronchus respiratory epithelial cells High Enhanced Q9NYF8 9774 +ENSG00000029363 BCLAF1 lung macrophages Medium Enhanced Q9NYF8 9774 +ENSG00000029363 BCLAF1 lung pneumocytes High Enhanced Q9NYF8 9774 +ENSG00000029364 SLC39A9 bronchus respiratory epithelial cells High Enhanced Q9NUM3 55334 +ENSG00000029364 SLC39A9 lung macrophages Medium Enhanced Q9NUM3 55334 +ENSG00000029364 SLC39A9 lung pneumocytes High Enhanced Q9NUM3 55334 +ENSG00000029725 RABEP1 bronchus respiratory epithelial cells Medium Enhanced Q15276 9135 +ENSG00000029725 RABEP1 lung macrophages Medium Enhanced Q15276 9135 +ENSG00000029725 RABEP1 lung pneumocytes Low Enhanced Q15276 9135 +ENSG00000029993 HMGB3 bronchus respiratory epithelial cells High Enhanced O15347 3149 +ENSG00000030110 BAK1 bronchus respiratory epithelial cells Medium Enhanced Q16611 578 +ENSG00000030110 BAK1 lung macrophages High Enhanced Q16611 578 +ENSG00000030110 BAK1 lung pneumocytes Low Enhanced Q16611 578 +ENSG00000031823 RANBP3 bronchus respiratory epithelial cells Medium Enhanced Q9H6Z4 8498 +ENSG00000031823 RANBP3 lung macrophages Medium Enhanced Q9H6Z4 8498 +ENSG00000031823 RANBP3 lung pneumocytes Low Enhanced Q9H6Z4 8498 +ENSG00000033030 ZCCHC8 bronchus respiratory epithelial cells High Supported Q6NZY4 55596 +ENSG00000033030 ZCCHC8 lung macrophages Medium Supported Q6NZY4 55596 +ENSG00000033030 ZCCHC8 lung pneumocytes High Supported Q6NZY4 55596 +ENSG00000033050 ABCF2 bronchus respiratory epithelial cells Low Enhanced Q9UG63 10061 +ENSG00000033050 ABCF2 lung macrophages Low Enhanced Q9UG63 10061 +ENSG00000033170 FUT8 bronchus respiratory epithelial cells Medium Enhanced Q9BYC5 2530 +ENSG00000033170 FUT8 lung macrophages High Enhanced Q9BYC5 2530 +ENSG00000033170 FUT8 lung pneumocytes Low Enhanced Q9BYC5 2530 +ENSG00000033327 GAB2 bronchus respiratory epithelial cells Medium Enhanced Q9UQC2 9846 +ENSG00000033327 GAB2 lung macrophages Medium Enhanced Q9UQC2 9846 +ENSG00000033327 GAB2 lung pneumocytes Low Enhanced Q9UQC2 9846 +ENSG00000033627 ATP6V0A1 bronchus respiratory epithelial cells Low Enhanced Q93050 535 +ENSG00000033627 ATP6V0A1 lung macrophages Medium Enhanced Q93050 535 +ENSG00000033627 ATP6V0A1 lung pneumocytes Low Enhanced Q93050 535 +ENSG00000033800 PIAS1 bronchus respiratory epithelial cells High Supported O75925 8554 +ENSG00000033800 PIAS1 lung macrophages High Supported O75925 8554 +ENSG00000033800 PIAS1 lung pneumocytes High Supported O75925 8554 +ENSG00000034239 EFCAB1 bronchus respiratory epithelial cells High Enhanced Q9HAE3 79645 +ENSG00000034533 ASTE1 bronchus respiratory epithelial cells Medium Enhanced Q2TB18 28990 +ENSG00000034533 ASTE1 lung macrophages Medium Enhanced Q2TB18 28990 +ENSG00000034693 PEX3 bronchus respiratory epithelial cells High Enhanced P56589 8504 +ENSG00000034693 PEX3 lung macrophages Low Enhanced P56589 8504 +ENSG00000035141 FAM136A bronchus respiratory epithelial cells High Enhanced Q96C01 84908 +ENSG00000035141 FAM136A lung macrophages Medium Enhanced Q96C01 84908 +ENSG00000035141 FAM136A lung pneumocytes Medium Enhanced Q96C01 84908 +ENSG00000035403 VCL bronchus respiratory epithelial cells Medium Enhanced P18206 7414 +ENSG00000035403 VCL lung pneumocytes Low Enhanced P18206 7414 +ENSG00000035687 ADSS bronchus respiratory epithelial cells Medium Enhanced P30520 159 +ENSG00000035687 ADSS lung macrophages Low Enhanced P30520 159 +ENSG00000035687 ADSS lung pneumocytes Low Enhanced P30520 159 +ENSG00000035928 RFC1 bronchus respiratory epithelial cells Medium Supported P35251 5981 +ENSG00000035928 RFC1 lung macrophages Low Supported P35251 5981 +ENSG00000035928 RFC1 lung pneumocytes Medium Supported P35251 5981 +ENSG00000036257 CUL3 bronchus respiratory epithelial cells High Supported Q13618 8452 +ENSG00000036257 CUL3 lung macrophages Medium Supported Q13618 8452 +ENSG00000036257 CUL3 lung pneumocytes Medium Supported Q13618 8452 +ENSG00000036448 MYOM2 bronchus respiratory epithelial cells Medium Enhanced E7EWH9 NA +ENSG00000036448 MYOM2 lung macrophages Low Enhanced E7EWH9 NA +ENSG00000037474 NSUN2 bronchus respiratory epithelial cells Medium Enhanced Q08J23 54888 +ENSG00000037474 NSUN2 lung macrophages Low Enhanced Q08J23 54888 +ENSG00000037474 NSUN2 lung pneumocytes Medium Enhanced Q08J23 54888 +ENSG00000038002 AGA bronchus respiratory epithelial cells Medium Enhanced P20933 175 +ENSG00000038002 AGA lung macrophages Medium Enhanced P20933 175 +ENSG00000038002 AGA lung pneumocytes Medium Enhanced P20933 175 +ENSG00000038358 EDC4 bronchus respiratory epithelial cells High Supported Q6P2E9 23644 +ENSG00000038358 EDC4 lung macrophages Medium Supported Q6P2E9 23644 +ENSG00000038358 EDC4 lung pneumocytes Low Supported Q6P2E9 23644 +ENSG00000038382 TRIO bronchus respiratory epithelial cells Medium Supported O75962 7204 +ENSG00000038382 TRIO lung macrophages High Supported O75962 7204 +ENSG00000038382 TRIO lung pneumocytes High Supported O75962 7204 +ENSG00000038427 VCAN lung macrophages Low Enhanced P13611 1462 +ENSG00000038945 MSR1 lung macrophages High Enhanced P21757 4481 +ENSG00000039068 CDH1 bronchus respiratory epithelial cells Medium Enhanced P12830 999 +ENSG00000039068 CDH1 lung macrophages Low Enhanced P12830 999 +ENSG00000039068 CDH1 lung pneumocytes High Enhanced P12830 999 +ENSG00000039123 SKIV2L2 bronchus respiratory epithelial cells High Supported P42285 23517 +ENSG00000039123 SKIV2L2 lung macrophages Medium Supported P42285 23517 +ENSG00000039123 SKIV2L2 lung pneumocytes Medium Supported P42285 23517 +ENSG00000039139 DNAH5 bronchus respiratory epithelial cells High Enhanced Q8TE73 1767 +ENSG00000039319 ZFYVE16 bronchus respiratory epithelial cells Medium Supported Q7Z3T8 9765 +ENSG00000039319 ZFYVE16 lung macrophages Low Supported Q7Z3T8 9765 +ENSG00000039319 ZFYVE16 lung pneumocytes Low Supported Q7Z3T8 9765 +ENSG00000039537 C6 lung macrophages Low Enhanced P13671 729 +ENSG00000039560 RAI14 bronchus respiratory epithelial cells Medium Supported Q9P0K7 26064 +ENSG00000039560 RAI14 lung macrophages Low Supported Q9P0K7 26064 +ENSG00000039650 PNKP bronchus respiratory epithelial cells High Supported Q96T60 11284 +ENSG00000039650 PNKP lung macrophages High Supported Q96T60 11284 +ENSG00000039650 PNKP lung pneumocytes High Supported Q96T60 11284 +ENSG00000040275 SPDL1 bronchus respiratory epithelial cells Medium Enhanced Q96EA4 54908 +ENSG00000040275 SPDL1 lung macrophages Medium Enhanced Q96EA4 54908 +ENSG00000040275 SPDL1 lung pneumocytes Medium Enhanced Q96EA4 54908 +ENSG00000041353 RAB27B lung macrophages Low Enhanced O00194 5874 +ENSG00000041357 PSMA4 bronchus respiratory epithelial cells Medium Supported P25789 5685 +ENSG00000041357 PSMA4 lung macrophages Medium Supported P25789 5685 +ENSG00000041880 PARP3 bronchus respiratory epithelial cells Medium Supported Q9Y6F1 10039 +ENSG00000041880 PARP3 lung macrophages Medium Supported Q9Y6F1 10039 +ENSG00000041880 PARP3 lung pneumocytes Medium Supported Q9Y6F1 10039 +ENSG00000042317 SPATA7 bronchus respiratory epithelial cells Medium Enhanced Q9P0W8 55812 +ENSG00000042493 CAPG lung macrophages High Enhanced P40121 822 +ENSG00000042980 ADAM28 bronchus respiratory epithelial cells Medium Enhanced Q9UKQ2 10863 +ENSG00000043462 LCP2 lung macrophages High Enhanced Q13094 3937 +ENSG00000043462 LCP2 lung pneumocytes High Enhanced Q13094 3937 +ENSG00000044574 HSPA5 bronchus respiratory epithelial cells Medium Enhanced P11021 3309 +ENSG00000044574 HSPA5 lung macrophages Medium Enhanced P11021 3309 +ENSG00000044574 HSPA5 lung pneumocytes Medium Enhanced P11021 3309 +ENSG00000046604 DSG2 bronchus respiratory epithelial cells High Enhanced Q14126 1829 +ENSG00000046604 DSG2 lung pneumocytes Low Enhanced Q14126 1829 +ENSG00000046889 PREX2 bronchus respiratory epithelial cells Medium Enhanced Q70Z35 80243 +ENSG00000046889 PREX2 lung macrophages Low Enhanced Q70Z35 80243 +ENSG00000046889 PREX2 lung pneumocytes Low Enhanced Q70Z35 80243 +ENSG00000047056 WDR37 bronchus respiratory epithelial cells Medium Enhanced Q9Y2I8 22884 +ENSG00000047056 WDR37 lung macrophages Medium Enhanced Q9Y2I8 22884 +ENSG00000047056 WDR37 lung pneumocytes Low Enhanced Q9Y2I8 22884 +ENSG00000047315 POLR2B bronchus respiratory epithelial cells High Supported P30876 5431 +ENSG00000047315 POLR2B lung macrophages Medium Supported P30876 5431 +ENSG00000047315 POLR2B lung pneumocytes High Supported P30876 5431 +ENSG00000047410 TPR bronchus respiratory epithelial cells High Enhanced P12270 7175 +ENSG00000047410 TPR lung macrophages Medium Enhanced P12270 7175 +ENSG00000047410 TPR lung pneumocytes Medium Enhanced P12270 7175 +ENSG00000047578 KIAA0556 bronchus respiratory epithelial cells Medium Enhanced O60303 23247 +ENSG00000047578 KIAA0556 lung macrophages Medium Enhanced O60303 23247 +ENSG00000047578 KIAA0556 lung pneumocytes Low Enhanced O60303 23247 +ENSG00000047579 DTNBP1 bronchus respiratory epithelial cells Medium Enhanced Q96EV8 84062 +ENSG00000047579 DTNBP1 lung macrophages Medium Enhanced Q96EV8 84062 +ENSG00000047648 ARHGAP6 bronchus respiratory epithelial cells Medium Enhanced O43182 395 +ENSG00000047648 ARHGAP6 lung macrophages Medium Enhanced O43182 395 +ENSG00000047648 ARHGAP6 lung pneumocytes Medium Enhanced O43182 395 +ENSG00000047849 MAP4 bronchus respiratory epithelial cells Medium Enhanced P27816 4134 +ENSG00000047849 MAP4 lung macrophages Medium Enhanced P27816 4134 +ENSG00000048028 USP28 bronchus respiratory epithelial cells High Enhanced Q96RU2 57646 +ENSG00000048028 USP28 lung macrophages Medium Enhanced Q96RU2 57646 +ENSG00000048544 MRPS10 bronchus respiratory epithelial cells High Enhanced P82664 55173 +ENSG00000048544 MRPS10 lung macrophages High Enhanced P82664 55173 +ENSG00000048544 MRPS10 lung pneumocytes High Enhanced P82664 55173 +ENSG00000048649 RSF1 bronchus respiratory epithelial cells Medium Enhanced Q96T23 51773 +ENSG00000048649 RSF1 lung macrophages High Enhanced Q96T23 51773 +ENSG00000048649 RSF1 lung pneumocytes High Enhanced Q96T23 51773 +ENSG00000048740 CELF2 lung macrophages Low Enhanced O95319 10659 +ENSG00000048740 CELF2 lung pneumocytes Low Enhanced O95319 10659 +ENSG00000049768 FOXP3 lung macrophages Low Enhanced Q9BZS1 50943 +ENSG00000049860 HEXB lung macrophages Medium Enhanced P07686 3074 +ENSG00000050130 JKAMP bronchus respiratory epithelial cells High Supported Q9P055 51528 +ENSG00000050130 JKAMP lung macrophages Medium Supported Q9P055 51528 +ENSG00000050327 ARHGEF5 bronchus respiratory epithelial cells High Enhanced Q12774 7984 +ENSG00000050327 ARHGEF5 lung macrophages Medium Enhanced Q12774 7984 +ENSG00000050327 ARHGEF5 lung pneumocytes Medium Enhanced Q12774 7984 +ENSG00000050344 NFE2L3 bronchus respiratory epithelial cells Medium Enhanced Q9Y4A8 9603 +ENSG00000050405 LIMA1 bronchus respiratory epithelial cells Medium Enhanced Q9UHB6 51474 +ENSG00000050405 LIMA1 lung macrophages Medium Enhanced Q9UHB6 51474 +ENSG00000050555 LAMC3 lung macrophages Low Enhanced Q9Y6N6 10319 +ENSG00000051180 RAD51 bronchus respiratory epithelial cells Low Enhanced Q06609 5888 +ENSG00000051180 RAD51 lung macrophages Low Enhanced Q06609 5888 +ENSG00000051523 CYBA lung macrophages High Enhanced P13498 1535 +ENSG00000052723 SIKE1 bronchus respiratory epithelial cells Medium Supported Q9BRV8 80143 +ENSG00000052723 SIKE1 lung macrophages Medium Supported Q9BRV8 80143 +ENSG00000052723 SIKE1 lung pneumocytes Medium Supported Q9BRV8 80143 +ENSG00000053371 AKR7A2 bronchus respiratory epithelial cells Medium Enhanced O43488 8574 +ENSG00000053371 AKR7A2 lung macrophages Low Enhanced O43488 8574 +ENSG00000053371 AKR7A2 lung pneumocytes Low Enhanced O43488 8574 +ENSG00000053918 KCNQ1 bronchus respiratory epithelial cells Medium Enhanced P51787 3784 +ENSG00000053918 KCNQ1 lung macrophages Medium Enhanced P51787 3784 +ENSG00000053918 KCNQ1 lung pneumocytes Medium Enhanced P51787 3784 +ENSG00000054118 THRAP3 bronchus respiratory epithelial cells High Supported Q9Y2W1 9967 +ENSG00000054118 THRAP3 lung macrophages High Supported Q9Y2W1 9967 +ENSG00000054118 THRAP3 lung pneumocytes High Supported Q9Y2W1 9967 +ENSG00000054219 LY75 bronchus respiratory epithelial cells Low Enhanced O60449 100526664; 4065 +ENSG00000054219 LY75 lung macrophages Medium Enhanced O60449 100526664; 4065 +ENSG00000054598 FOXC1 bronchus respiratory epithelial cells Medium Enhanced Q12948 2296 +ENSG00000054598 FOXC1 lung pneumocytes Medium Enhanced Q12948 2296 +ENSG00000054654 SYNE2 bronchus respiratory epithelial cells Medium Enhanced Q8WXH0 23224 +ENSG00000054654 SYNE2 lung pneumocytes Low Enhanced Q8WXH0 23224 +ENSG00000055044 NOP58 bronchus respiratory epithelial cells High Supported Q9Y2X3 51602 +ENSG00000055044 NOP58 lung macrophages Medium Supported Q9Y2X3 51602 +ENSG00000055044 NOP58 lung pneumocytes Medium Supported Q9Y2X3 51602 +ENSG00000055130 CUL1 bronchus respiratory epithelial cells Low Supported Q13616 8454 +ENSG00000055130 CUL1 lung macrophages Low Supported Q13616 8454 +ENSG00000055130 CUL1 lung pneumocytes Medium Supported Q13616 8454 +ENSG00000055955 ITIH4 bronchus respiratory epithelial cells Low Enhanced Q14624 3700 +ENSG00000056097 ZFR lung macrophages Medium Supported Q96KR1 51663 +ENSG00000056097 ZFR lung pneumocytes High Supported Q96KR1 51663 +ENSG00000056277 ZNF280C bronchus respiratory epithelial cells Medium Enhanced Q8ND82 55609 +ENSG00000056277 ZNF280C lung macrophages Medium Enhanced Q8ND82 55609 +ENSG00000056277 ZNF280C lung pneumocytes Medium Enhanced Q8ND82 55609 +ENSG00000057149 SERPINB3 bronchus respiratory epithelial cells High Enhanced P29508 6317 +ENSG00000057294 PKP2 bronchus respiratory epithelial cells Medium Enhanced Q99959 5318 +ENSG00000057294 PKP2 lung macrophages Low Enhanced Q99959 5318 +ENSG00000057608 GDI2 bronchus respiratory epithelial cells Medium Supported P50395 2665 +ENSG00000057608 GDI2 lung macrophages Low Supported P50395 2665 +ENSG00000057663 ATG5 bronchus respiratory epithelial cells Medium Enhanced Q9H1Y0 9474 +ENSG00000057663 ATG5 lung macrophages Medium Enhanced Q9H1Y0 9474 +ENSG00000057663 ATG5 lung pneumocytes Low Enhanced Q9H1Y0 9474 +ENSG00000058085 LAMC2 bronchus respiratory epithelial cells Medium Enhanced Q13753 3918 +ENSG00000058453 CROCC bronchus respiratory epithelial cells High Enhanced Q5TZA2 9696 +ENSG00000058668 ATP2B4 bronchus respiratory epithelial cells High Enhanced P23634 493 +ENSG00000058668 ATP2B4 lung macrophages Low Enhanced P23634 493 +ENSG00000058668 ATP2B4 lung pneumocytes Medium Enhanced P23634 493 +ENSG00000059377 TBXAS1 lung macrophages Medium Enhanced P24557 6916 +ENSG00000059728 MXD1 bronchus respiratory epithelial cells Medium Enhanced Q05195 4084 +ENSG00000059728 MXD1 lung macrophages Low Enhanced Q05195 4084 +ENSG00000059728 MXD1 lung pneumocytes Medium Enhanced Q05195 4084 +ENSG00000060069 CTDP1 lung macrophages Medium Supported Q9Y5B0 9150 +ENSG00000060069 CTDP1 lung pneumocytes Medium Supported Q9Y5B0 9150 +ENSG00000060237 WNK1 bronchus respiratory epithelial cells Medium Enhanced Q9H4A3 65125 +ENSG00000060237 WNK1 lung macrophages Low Enhanced Q9H4A3 65125 +ENSG00000060237 WNK1 lung pneumocytes High Enhanced Q9H4A3 65125 +ENSG00000060339 CCAR1 bronchus respiratory epithelial cells High Supported Q8IX12 55749 +ENSG00000060339 CCAR1 lung macrophages High Supported Q8IX12 55749 +ENSG00000060339 CCAR1 lung pneumocytes High Supported Q8IX12 55749 +ENSG00000060491 OGFR bronchus respiratory epithelial cells Medium Enhanced Q9NZT2 11054 +ENSG00000060491 OGFR lung macrophages High Enhanced Q9NZT2 11054 +ENSG00000060688 SNRNP40 bronchus respiratory epithelial cells High Supported Q96DI7 9410 +ENSG00000060688 SNRNP40 lung macrophages Medium Supported Q96DI7 9410 +ENSG00000060688 SNRNP40 lung pneumocytes Medium Supported Q96DI7 9410 +ENSG00000060762 MPC1 bronchus respiratory epithelial cells High Enhanced Q9Y5U8 51660 +ENSG00000060762 MPC1 lung macrophages Medium Enhanced Q9Y5U8 51660 +ENSG00000060762 MPC1 lung pneumocytes Low Enhanced Q9Y5U8 51660 +ENSG00000060971 ACAA1 bronchus respiratory epithelial cells Low Enhanced P09110 30 +ENSG00000060971 ACAA1 lung macrophages Medium Enhanced P09110 30 +ENSG00000060971 ACAA1 lung pneumocytes Medium Enhanced P09110 30 +ENSG00000061676 NCKAP1 bronchus respiratory epithelial cells Medium Enhanced Q9Y2A7 10787 +ENSG00000061676 NCKAP1 lung pneumocytes Low Enhanced Q9Y2A7 10787 +ENSG00000061794 MRPS35 bronchus respiratory epithelial cells High Enhanced P82673 60488 +ENSG00000061794 MRPS35 lung macrophages High Enhanced P82673 60488 +ENSG00000062038 CDH3 bronchus respiratory epithelial cells High Enhanced P22223 1001 +ENSG00000062485 CS bronchus respiratory epithelial cells High Enhanced O75390 1431 +ENSG00000062485 CS lung macrophages High Enhanced O75390 1431 +ENSG00000062485 CS lung pneumocytes Medium Enhanced O75390 1431 +ENSG00000062650 WAPL bronchus respiratory epithelial cells Medium Enhanced Q7Z5K2 23063 +ENSG00000062650 WAPL lung macrophages Medium Enhanced Q7Z5K2 23063 +ENSG00000062650 WAPL lung pneumocytes Medium Enhanced Q7Z5K2 23063 +ENSG00000062822 POLD1 bronchus respiratory epithelial cells Medium Enhanced P28340 5424 +ENSG00000062822 POLD1 lung macrophages Medium Enhanced P28340 5424 +ENSG00000062822 POLD1 lung pneumocytes High Enhanced P28340 5424 +ENSG00000063015 SEZ6 lung macrophages Low Enhanced Q53EL9 124925 +ENSG00000063015 SEZ6 lung pneumocytes Low Enhanced Q53EL9 124925 +ENSG00000063241 ISOC2 bronchus respiratory epithelial cells High Enhanced Q96AB3 79763 +ENSG00000063241 ISOC2 lung macrophages High Enhanced Q96AB3 79763 +ENSG00000063241 ISOC2 lung pneumocytes High Enhanced Q96AB3 79763 +ENSG00000063244 U2AF2 bronchus respiratory epithelial cells Medium Supported P26368 11338 +ENSG00000063244 U2AF2 lung macrophages Medium Supported P26368 11338 +ENSG00000063244 U2AF2 lung pneumocytes Medium Supported P26368 11338 +ENSG00000064199 SPA17 bronchus respiratory epithelial cells High Enhanced Q15506 53340 +ENSG00000064300 NGFR bronchus respiratory epithelial cells Low Enhanced P08138 4804 +ENSG00000064393 HIPK2 bronchus respiratory epithelial cells High Supported Q9H2X6 28996 +ENSG00000064393 HIPK2 lung macrophages High Supported Q9H2X6 28996 +ENSG00000064393 HIPK2 lung pneumocytes High Supported Q9H2X6 28996 +ENSG00000064601 CTSA bronchus respiratory epithelial cells Medium Enhanced P10619 5476 +ENSG00000064601 CTSA lung macrophages Medium Enhanced P10619 5476 +ENSG00000064601 CTSA lung pneumocytes Medium Enhanced P10619 5476 +ENSG00000064607 SUGP2 bronchus respiratory epithelial cells Medium Enhanced Q8IX01 10147 +ENSG00000064607 SUGP2 lung pneumocytes Low Enhanced Q8IX01 10147 +ENSG00000064687 ABCA7 bronchus respiratory epithelial cells Low Enhanced Q8IZY2 10347 +ENSG00000064687 ABCA7 lung macrophages Low Enhanced Q8IZY2 10347 +ENSG00000064703 DDX20 bronchus respiratory epithelial cells Low Enhanced Q9UHI6 11218 +ENSG00000064726 BTBD1 bronchus respiratory epithelial cells Medium Enhanced Q9H0C5 53339 +ENSG00000064726 BTBD1 lung macrophages Low Enhanced Q9H0C5 53339 +ENSG00000064787 BCAS1 bronchus respiratory epithelial cells High Enhanced O75363 8537 +ENSG00000065054 SLC9A3R2 bronchus respiratory epithelial cells Medium Enhanced Q15599 9351 +ENSG00000065057 NTHL1 bronchus respiratory epithelial cells Medium Supported P78549 4913 +ENSG00000065057 NTHL1 lung macrophages Medium Supported P78549 4913 +ENSG00000065057 NTHL1 lung pneumocytes Medium Supported P78549 4913 +ENSG00000065154 OAT bronchus respiratory epithelial cells Medium Enhanced P04181 4942 +ENSG00000065154 OAT lung macrophages Low Enhanced P04181 4942 +ENSG00000065427 KARS bronchus respiratory epithelial cells High Enhanced Q15046 3735 +ENSG00000065427 KARS lung macrophages High Enhanced Q15046 3735 +ENSG00000065427 KARS lung pneumocytes Medium Enhanced Q15046 3735 +ENSG00000065485 PDIA5 bronchus respiratory epithelial cells Low Enhanced Q14554 10954 +ENSG00000065485 PDIA5 lung pneumocytes High Enhanced Q14554 10954 +ENSG00000065518 NDUFB4 bronchus respiratory epithelial cells High Enhanced O95168 4710 +ENSG00000065518 NDUFB4 lung macrophages Low Enhanced O95168 4710 +ENSG00000065518 NDUFB4 lung pneumocytes Low Enhanced O95168 4710 +ENSG00000065526 SPEN bronchus respiratory epithelial cells High Supported Q96T58 23013 +ENSG00000065526 SPEN lung macrophages Medium Supported Q96T58 23013 +ENSG00000065526 SPEN lung pneumocytes High Supported Q96T58 23013 +ENSG00000065548 ZC3H15 bronchus respiratory epithelial cells High Enhanced Q8WU90 55854 +ENSG00000065548 ZC3H15 lung macrophages Medium Enhanced Q8WU90 55854 +ENSG00000065548 ZC3H15 lung pneumocytes Medium Enhanced Q8WU90 55854 +ENSG00000065559 MAP2K4 bronchus respiratory epithelial cells Low Enhanced P45985 6416 +ENSG00000065559 MAP2K4 lung macrophages Low Enhanced P45985 6416 +ENSG00000065559 MAP2K4 lung pneumocytes Low Enhanced P45985 6416 +ENSG00000065833 ME1 lung macrophages Low Enhanced P48163 4199 +ENSG00000065978 YBX1 bronchus respiratory epithelial cells Medium Supported P67809 4904 +ENSG00000065978 YBX1 lung macrophages Medium Supported P67809 4904 +ENSG00000065978 YBX1 lung pneumocytes Low Supported P67809 4904 +ENSG00000066084 DIP2B bronchus respiratory epithelial cells High Enhanced Q9P265 57609 +ENSG00000066084 DIP2B lung macrophages Medium Enhanced Q9P265 57609 +ENSG00000066084 DIP2B lung pneumocytes Medium Enhanced Q9P265 57609 +ENSG00000066117 SMARCD1 bronchus respiratory epithelial cells High Supported Q96GM5 6602 +ENSG00000066117 SMARCD1 lung macrophages Medium Supported Q96GM5 6602 +ENSG00000066117 SMARCD1 lung pneumocytes Medium Supported Q96GM5 6602 +ENSG00000066294 CD84 lung macrophages Low Enhanced Q9UIB8 8832 +ENSG00000066294 CD84 lung pneumocytes Low Enhanced Q9UIB8 8832 +ENSG00000066336 SPI1 lung macrophages High Enhanced P17947 6688 +ENSG00000066379 ZNRD1 bronchus respiratory epithelial cells High Supported NA NA +ENSG00000066379 ZNRD1 lung macrophages Medium Supported NA NA +ENSG00000066379 ZNRD1 lung pneumocytes Medium Supported NA NA +ENSG00000066455 GOLGA5 lung macrophages High Enhanced Q8TBA6 9950 +ENSG00000066455 GOLGA5 lung pneumocytes Medium Enhanced Q8TBA6 9950 +ENSG00000066777 ARFGEF1 bronchus respiratory epithelial cells Medium Supported Q9Y6D6 10565 +ENSG00000066777 ARFGEF1 lung macrophages Medium Supported Q9Y6D6 10565 +ENSG00000066777 ARFGEF1 lung pneumocytes Low Supported Q9Y6D6 10565 +ENSG00000067066 SP100 bronchus respiratory epithelial cells Medium Enhanced P23497 6672 +ENSG00000067066 SP100 lung macrophages Medium Enhanced P23497 6672 +ENSG00000067066 SP100 lung pneumocytes Medium Enhanced P23497 6672 +ENSG00000067082 KLF6 bronchus respiratory epithelial cells Medium Supported Q99612 1316 +ENSG00000067082 KLF6 lung macrophages Low Supported Q99612 1316 +ENSG00000067082 KLF6 lung pneumocytes Medium Supported Q99612 1316 +ENSG00000067113 PLPP1 bronchus respiratory epithelial cells Low Enhanced O14494 8611 +ENSG00000067369 TP53BP1 bronchus respiratory epithelial cells High Supported Q12888 7158 +ENSG00000067369 TP53BP1 lung macrophages Medium Supported Q12888 7158 +ENSG00000067369 TP53BP1 lung pneumocytes High Supported Q12888 7158 +ENSG00000067606 PRKCZ bronchus respiratory epithelial cells Medium Enhanced Q05513 5590 +ENSG00000067704 IARS2 bronchus respiratory epithelial cells Medium Enhanced Q9NSE4 55699 +ENSG00000067704 IARS2 lung macrophages Medium Enhanced Q9NSE4 55699 +ENSG00000067704 IARS2 lung pneumocytes Low Enhanced Q9NSE4 55699 +ENSG00000067829 IDH3G bronchus respiratory epithelial cells High Enhanced P51553 3421 +ENSG00000067829 IDH3G lung macrophages Medium Enhanced P51553 3421 +ENSG00000068366 ACSL4 bronchus respiratory epithelial cells Medium Enhanced O60488 2182 +ENSG00000068366 ACSL4 lung macrophages Medium Enhanced O60488 2182 +ENSG00000068366 ACSL4 lung pneumocytes Low Enhanced O60488 2182 +ENSG00000068383 INPP5A bronchus respiratory epithelial cells Medium Enhanced Q14642 3632 +ENSG00000068383 INPP5A lung macrophages High Enhanced Q14642 3632 +ENSG00000068383 INPP5A lung pneumocytes High Enhanced Q14642 3632 +ENSG00000068394 GPKOW bronchus respiratory epithelial cells Medium Enhanced Q92917 27238 +ENSG00000068394 GPKOW lung macrophages High Enhanced Q92917 27238 +ENSG00000068394 GPKOW lung pneumocytes High Enhanced Q92917 27238 +ENSG00000068400 GRIPAP1 bronchus respiratory epithelial cells Medium Enhanced Q4V328 56850 +ENSG00000068400 GRIPAP1 lung macrophages Low Enhanced Q4V328 56850 +ENSG00000068654 POLR1A bronchus respiratory epithelial cells High Supported O95602 25885 +ENSG00000068654 POLR1A lung macrophages Low Supported O95602 25885 +ENSG00000068654 POLR1A lung pneumocytes Medium Supported O95602 25885 +ENSG00000068724 TTC7A bronchus respiratory epithelial cells High Enhanced Q9ULT0 57217 +ENSG00000068724 TTC7A lung macrophages High Enhanced Q9ULT0 57217 +ENSG00000068724 TTC7A lung pneumocytes Medium Enhanced Q9ULT0 57217 +ENSG00000068912 ERLEC1 bronchus respiratory epithelial cells Medium Enhanced Q96DZ1 27248 +ENSG00000068912 ERLEC1 lung macrophages Low Enhanced Q96DZ1 27248 +ENSG00000069275 NUCKS1 bronchus respiratory epithelial cells High Supported Q9H1E3 64710 +ENSG00000069275 NUCKS1 lung macrophages Low Supported Q9H1E3 64710 +ENSG00000069275 NUCKS1 lung pneumocytes High Supported Q9H1E3 64710 +ENSG00000069329 VPS35 bronchus respiratory epithelial cells Medium Enhanced Q96QK1 55737 +ENSG00000069329 VPS35 lung macrophages High Enhanced Q96QK1 55737 +ENSG00000069329 VPS35 lung pneumocytes Low Enhanced Q96QK1 55737 +ENSG00000069535 MAOB bronchus respiratory epithelial cells High Enhanced P27338 4129 +ENSG00000069535 MAOB lung macrophages Low Enhanced P27338 4129 +ENSG00000069535 MAOB lung pneumocytes Medium Enhanced P27338 4129 +ENSG00000069702 TGFBR3 bronchus respiratory epithelial cells Low Supported Q03167 7049 +ENSG00000069702 TGFBR3 lung macrophages Medium Supported Q03167 7049 +ENSG00000069702 TGFBR3 lung pneumocytes Low Supported Q03167 7049 +ENSG00000069849 ATP1B3 bronchus respiratory epithelial cells Medium Enhanced P54709 483 +ENSG00000069849 ATP1B3 lung macrophages Medium Enhanced P54709 483 +ENSG00000069849 ATP1B3 lung pneumocytes Medium Enhanced P54709 483 +ENSG00000070018 LRP6 bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000070018 LRP6 lung macrophages Medium Enhanced NA NA +ENSG00000070087 PFN2 bronchus respiratory epithelial cells Medium Enhanced P35080 5217 +ENSG00000070087 PFN2 lung macrophages Medium Enhanced P35080 5217 +ENSG00000070495 JMJD6 bronchus respiratory epithelial cells Medium Supported Q6NYC1 23210 +ENSG00000070495 JMJD6 lung macrophages High Supported Q6NYC1 23210 +ENSG00000070501 POLB bronchus respiratory epithelial cells Medium Enhanced P06746 5423 +ENSG00000070501 POLB lung macrophages Low Enhanced P06746 5423 +ENSG00000070501 POLB lung pneumocytes Low Enhanced P06746 5423 +ENSG00000070540 WIPI1 bronchus respiratory epithelial cells Medium Enhanced Q5MNZ9 55062 +ENSG00000070540 WIPI1 lung macrophages Low Enhanced Q5MNZ9 55062 +ENSG00000070540 WIPI1 lung pneumocytes Medium Enhanced Q5MNZ9 55062 +ENSG00000070756 PABPC1 bronchus respiratory epithelial cells Medium Enhanced P11940 26986 +ENSG00000070756 PABPC1 lung macrophages Medium Enhanced P11940 26986 +ENSG00000070756 PABPC1 lung pneumocytes Low Enhanced P11940 26986 +ENSG00000070785 EIF2B3 bronchus respiratory epithelial cells High Supported Q9NR50 8891 +ENSG00000070785 EIF2B3 lung macrophages Medium Supported Q9NR50 8891 +ENSG00000070785 EIF2B3 lung pneumocytes Low Supported Q9NR50 8891 +ENSG00000070808 CAMK2A bronchus respiratory epithelial cells High Enhanced Q9UQM7 815 +ENSG00000070808 CAMK2A lung macrophages High Enhanced Q9UQM7 815 +ENSG00000070814 TCOF1 bronchus respiratory epithelial cells Medium Enhanced Q13428 6949 +ENSG00000070814 TCOF1 lung macrophages Medium Enhanced Q13428 6949 +ENSG00000070814 TCOF1 lung pneumocytes Low Enhanced Q13428 6949 +ENSG00000070882 OSBPL3 bronchus respiratory epithelial cells Medium Enhanced Q9H4L5 26031 +ENSG00000070882 OSBPL3 lung macrophages Low Enhanced Q9H4L5 26031 +ENSG00000070950 RAD18 bronchus respiratory epithelial cells Medium Supported Q9NS91 56852 +ENSG00000070950 RAD18 lung macrophages Medium Supported Q9NS91 56852 +ENSG00000070961 ATP2B1 bronchus respiratory epithelial cells Medium Enhanced P20020 490 +ENSG00000070961 ATP2B1 lung macrophages Medium Enhanced P20020 490 +ENSG00000070961 ATP2B1 lung pneumocytes Medium Enhanced P20020 490 +ENSG00000071073 MGAT4A bronchus respiratory epithelial cells Medium Enhanced Q9UM21 11320 +ENSG00000071073 MGAT4A lung macrophages Medium Enhanced Q9UM21 11320 +ENSG00000071282 LMCD1 bronchus respiratory epithelial cells Medium Enhanced Q9NZU5 29995 +ENSG00000071282 LMCD1 lung pneumocytes Medium Enhanced Q9NZU5 29995 +ENSG00000071626 DAZAP1 bronchus respiratory epithelial cells High Enhanced Q96EP5 26528 +ENSG00000071626 DAZAP1 lung macrophages High Enhanced Q96EP5 26528 +ENSG00000071626 DAZAP1 lung pneumocytes Medium Enhanced Q96EP5 26528 +ENSG00000071655 MBD3 bronchus respiratory epithelial cells Low Supported O95983 53615 +ENSG00000071655 MBD3 lung macrophages Low Supported O95983 53615 +ENSG00000071655 MBD3 lung pneumocytes Low Supported O95983 53615 +ENSG00000071859 FAM50A bronchus respiratory epithelial cells High Supported Q14320 9130 +ENSG00000071859 FAM50A lung macrophages High Supported Q14320 9130 +ENSG00000071859 FAM50A lung pneumocytes High Supported Q14320 9130 +ENSG00000072195 SPEG bronchus respiratory epithelial cells Medium Enhanced Q15772 10290 +ENSG00000072195 SPEG lung macrophages Low Enhanced Q15772 10290 +ENSG00000072274 TFRC bronchus respiratory epithelial cells Low Enhanced P02786 7037 +ENSG00000072274 TFRC lung macrophages Medium Enhanced P02786 7037 +ENSG00000072501 SMC1A bronchus respiratory epithelial cells High Supported Q14683 8243 +ENSG00000072501 SMC1A lung macrophages Medium Supported Q14683 8243 +ENSG00000072501 SMC1A lung pneumocytes Medium Supported Q14683 8243 +ENSG00000072682 P4HA2 bronchus respiratory epithelial cells Medium Enhanced O15460 8974 +ENSG00000072694 FCGR2B bronchus respiratory epithelial cells Low Enhanced P31994 2213 +ENSG00000072694 FCGR2B lung macrophages Low Enhanced P31994 2213 +ENSG00000072778 ACADVL bronchus respiratory epithelial cells Medium Enhanced P49748 37 +ENSG00000072778 ACADVL lung macrophages High Enhanced P49748 37 +ENSG00000072778 ACADVL lung pneumocytes Medium Enhanced P49748 37 +ENSG00000072786 STK10 lung macrophages Medium Enhanced O94804 6793 +ENSG00000072849 DERL2 bronchus respiratory epithelial cells Medium Enhanced Q9GZP9 51009 +ENSG00000072849 DERL2 lung macrophages Low Enhanced Q9GZP9 51009 +ENSG00000072858 SIDT1 bronchus respiratory epithelial cells Medium Enhanced Q9NXL6 54847 +ENSG00000073050 XRCC1 bronchus respiratory epithelial cells High Supported P18887 7515 +ENSG00000073050 XRCC1 lung macrophages High Supported P18887 7515 +ENSG00000073050 XRCC1 lung pneumocytes High Supported P18887 7515 +ENSG00000073060 SCARB1 bronchus respiratory epithelial cells Medium Enhanced Q8WTV0 949 +ENSG00000073150 PANX2 bronchus respiratory epithelial cells Low Enhanced Q96RD6 56666 +ENSG00000073282 TP63 bronchus respiratory epithelial cells High Enhanced Q9H3D4 8626 +ENSG00000073578 SDHA bronchus respiratory epithelial cells High Enhanced P31040 6389 +ENSG00000073578 SDHA lung macrophages Medium Enhanced P31040 6389 +ENSG00000073578 SDHA lung pneumocytes Low Enhanced P31040 6389 +ENSG00000073584 SMARCE1 bronchus respiratory epithelial cells High Enhanced Q969G3 6605 +ENSG00000073584 SMARCE1 lung macrophages High Enhanced Q969G3 6605 +ENSG00000073584 SMARCE1 lung pneumocytes High Enhanced Q969G3 6605 +ENSG00000073754 CD5L lung macrophages Low Enhanced O43866 922 +ENSG00000073792 IGF2BP2 bronchus respiratory epithelial cells Medium Enhanced Q9Y6M1 10644 +ENSG00000073792 IGF2BP2 lung macrophages Medium Enhanced Q9Y6M1 10644 +ENSG00000073792 IGF2BP2 lung pneumocytes Low Enhanced Q9Y6M1 10644 +ENSG00000073849 ST6GAL1 bronchus respiratory epithelial cells Low Supported P15907 6480 +ENSG00000073849 ST6GAL1 lung pneumocytes Low Supported P15907 6480 +ENSG00000073861 TBX21 lung macrophages Low Enhanced Q9UL17 30009 +ENSG00000073921 PICALM bronchus respiratory epithelial cells Medium Enhanced Q13492 8301 +ENSG00000073921 PICALM lung macrophages Medium Enhanced Q13492 8301 +ENSG00000073921 PICALM lung pneumocytes Low Enhanced Q13492 8301 +ENSG00000073969 NSF bronchus respiratory epithelial cells Low Enhanced NA NA +ENSG00000073969 NSF lung macrophages Low Enhanced NA NA +ENSG00000073969 NSF lung pneumocytes Low Enhanced NA NA +ENSG00000074071 MRPS34 bronchus respiratory epithelial cells High Supported P82930 65993 +ENSG00000074071 MRPS34 lung macrophages Medium Supported P82930 65993 +ENSG00000074266 EED bronchus respiratory epithelial cells Medium Supported O75530 8726 +ENSG00000074266 EED lung macrophages Low Supported O75530 8726 +ENSG00000074266 EED lung pneumocytes Medium Supported O75530 8726 +ENSG00000074276 CDHR2 bronchus respiratory epithelial cells Low Enhanced Q9BYE9 54825 +ENSG00000074356 NCBP3 bronchus respiratory epithelial cells High Supported Q53F19 55421 +ENSG00000074356 NCBP3 lung macrophages High Supported Q53F19 55421 +ENSG00000074356 NCBP3 lung pneumocytes High Supported Q53F19 55421 +ENSG00000074416 MGLL bronchus respiratory epithelial cells Low Enhanced Q99685 11343 +ENSG00000074416 MGLL lung macrophages Medium Enhanced Q99685 11343 +ENSG00000074416 MGLL lung pneumocytes Low Enhanced Q99685 11343 +ENSG00000074582 BCS1L lung macrophages High Enhanced Q9Y276 617 +ENSG00000074582 BCS1L lung pneumocytes Medium Enhanced Q9Y276 617 +ENSG00000074660 SCARF1 bronchus respiratory epithelial cells Low Enhanced NA NA +ENSG00000074695 LMAN1 bronchus respiratory epithelial cells Medium Supported P49257 3998 +ENSG00000074695 LMAN1 lung macrophages Medium Supported P49257 3998 +ENSG00000074695 LMAN1 lung pneumocytes Medium Supported P49257 3998 +ENSG00000074696 HACD3 bronchus respiratory epithelial cells Medium Enhanced Q9P035 51495 +ENSG00000074696 HACD3 lung macrophages Medium Enhanced Q9P035 51495 +ENSG00000074696 HACD3 lung pneumocytes Medium Enhanced Q9P035 51495 +ENSG00000074800 ENO1 bronchus respiratory epithelial cells Medium Enhanced P06733 2023 +ENSG00000074800 ENO1 lung macrophages Low Enhanced P06733 2023 +ENSG00000074800 ENO1 lung pneumocytes High Enhanced P06733 2023 +ENSG00000075151 EIF4G3 bronchus respiratory epithelial cells Low Enhanced O43432 8672 +ENSG00000075188 NUP37 bronchus respiratory epithelial cells Medium Enhanced Q8NFH4 79023 +ENSG00000075239 ACAT1 bronchus respiratory epithelial cells High Enhanced P24752 38 +ENSG00000075239 ACAT1 lung macrophages High Enhanced P24752 38 +ENSG00000075239 ACAT1 lung pneumocytes Medium Enhanced P24752 38 +ENSG00000075292 ZNF638 bronchus respiratory epithelial cells High Supported Q14966 27332 +ENSG00000075292 ZNF638 lung macrophages Low Supported Q14966 27332 +ENSG00000075292 ZNF638 lung pneumocytes Medium Supported Q14966 27332 +ENSG00000075340 ADD2 bronchus respiratory epithelial cells Low Enhanced P35612 119 +ENSG00000075391 RASAL2 bronchus respiratory epithelial cells Medium Enhanced Q9UJF2 9462 +ENSG00000075391 RASAL2 lung macrophages Low Enhanced Q9UJF2 9462 +ENSG00000075426 FOSL2 bronchus respiratory epithelial cells High Supported P15408 2355 +ENSG00000075426 FOSL2 lung macrophages Low Supported P15408 2355 +ENSG00000075539 FRYL bronchus respiratory epithelial cells Medium Supported O94915 285527 +ENSG00000075539 FRYL lung macrophages Medium Supported O94915 285527 +ENSG00000075539 FRYL lung pneumocytes Low Supported O94915 285527 +ENSG00000075618 FSCN1 lung pneumocytes Low Enhanced Q16658 6624 +ENSG00000075624 ACTB lung macrophages Low Supported P60709 60 +ENSG00000075651 PLD1 bronchus respiratory epithelial cells Medium Enhanced Q13393 5337 +ENSG00000075651 PLD1 lung macrophages Low Enhanced Q13393 5337 +ENSG00000075651 PLD1 lung pneumocytes Low Enhanced Q13393 5337 +ENSG00000075702 WDR62 bronchus respiratory epithelial cells Low Enhanced O43379 284403 +ENSG00000075702 WDR62 lung macrophages Low Enhanced O43379 284403 +ENSG00000075702 WDR62 lung pneumocytes Low Enhanced O43379 284403 +ENSG00000075711 DLG1 bronchus respiratory epithelial cells High Supported Q12959 1739 +ENSG00000075711 DLG1 lung macrophages High Supported Q12959 1739 +ENSG00000075711 DLG1 lung pneumocytes Low Supported Q12959 1739 +ENSG00000075785 RAB7A bronchus respiratory epithelial cells High Supported P51149 7879 +ENSG00000075785 RAB7A lung macrophages High Supported P51149 7879 +ENSG00000075785 RAB7A lung pneumocytes High Supported P51149 7879 +ENSG00000075790 BCAP29 bronchus respiratory epithelial cells Medium Enhanced B7Z2L0 NA +ENSG00000075790 BCAP29 lung macrophages Medium Enhanced B7Z2L0 NA +ENSG00000075790 BCAP29 lung pneumocytes Low Enhanced B7Z2L0 NA +ENSG00000075945 KIFAP3 bronchus respiratory epithelial cells Medium Supported Q92845 22920 +ENSG00000075945 KIFAP3 lung macrophages Medium Supported Q92845 22920 +ENSG00000075975 MKRN2 bronchus respiratory epithelial cells Medium Enhanced Q9H000 23609 +ENSG00000075975 MKRN2 lung macrophages Medium Enhanced Q9H000 23609 +ENSG00000075975 MKRN2 lung pneumocytes Low Enhanced Q9H000 23609 +ENSG00000076003 MCM6 bronchus respiratory epithelial cells Medium Enhanced Q14566 4175 +ENSG00000076003 MCM6 lung pneumocytes Medium Enhanced Q14566 4175 +ENSG00000076043 REXO2 bronchus respiratory epithelial cells Medium Enhanced Q9Y3B8 25996 +ENSG00000076043 REXO2 lung macrophages Medium Enhanced Q9Y3B8 25996 +ENSG00000076043 REXO2 lung pneumocytes Medium Enhanced Q9Y3B8 25996 +ENSG00000076053 RBM7 bronchus respiratory epithelial cells Medium Supported Q9Y580 10179 +ENSG00000076053 RBM7 lung pneumocytes Medium Supported Q9Y580 10179 +ENSG00000076242 MLH1 bronchus respiratory epithelial cells High Supported P40692 4292 +ENSG00000076242 MLH1 lung macrophages Medium Supported P40692 4292 +ENSG00000076242 MLH1 lung pneumocytes Medium Supported P40692 4292 +ENSG00000076513 ANKRD13A bronchus respiratory epithelial cells Medium Enhanced Q8IZ07 88455 +ENSG00000076513 ANKRD13A lung macrophages Low Enhanced Q8IZ07 88455 +ENSG00000076513 ANKRD13A lung pneumocytes Low Enhanced Q8IZ07 88455 +ENSG00000076554 TPD52 bronchus respiratory epithelial cells Medium Enhanced P55327 7163 +ENSG00000076554 TPD52 lung pneumocytes High Enhanced P55327 7163 +ENSG00000076555 ACACB bronchus respiratory epithelial cells Low Enhanced O00763 32 +ENSG00000076604 TRAF4 bronchus respiratory epithelial cells Medium Enhanced Q9BUZ4 9618 +ENSG00000076604 TRAF4 lung macrophages Medium Enhanced Q9BUZ4 9618 +ENSG00000076770 MBNL3 bronchus respiratory epithelial cells Low Enhanced Q9NUK0 55796 +ENSG00000076826 CAMSAP3 bronchus respiratory epithelial cells Medium Enhanced Q9P1Y5 57662 +ENSG00000076826 CAMSAP3 lung pneumocytes Low Enhanced Q9P1Y5 57662 +ENSG00000076864 RAP1GAP lung pneumocytes Medium Enhanced P47736 5909 +ENSG00000076928 ARHGEF1 bronchus respiratory epithelial cells Low Enhanced Q92888 9138 +ENSG00000076928 ARHGEF1 lung macrophages Medium Enhanced Q92888 9138 +ENSG00000076928 ARHGEF1 lung pneumocytes Medium Enhanced Q92888 9138 +ENSG00000076984 MAP2K7 bronchus respiratory epithelial cells Medium Supported O14733 5609 +ENSG00000076984 MAP2K7 lung macrophages Medium Supported O14733 5609 +ENSG00000077063 CTTNBP2 bronchus respiratory epithelial cells Medium Enhanced Q8WZ74 83992 +ENSG00000077063 CTTNBP2 lung macrophages Medium Enhanced Q8WZ74 83992 +ENSG00000077063 CTTNBP2 lung pneumocytes Low Enhanced Q8WZ74 83992 +ENSG00000077092 RARB bronchus respiratory epithelial cells Medium Enhanced P10826 5915 +ENSG00000077092 RARB lung macrophages Medium Enhanced P10826 5915 +ENSG00000077092 RARB lung pneumocytes Medium Enhanced P10826 5915 +ENSG00000077097 TOP2B bronchus respiratory epithelial cells Medium Supported Q02880 7155 +ENSG00000077097 TOP2B lung macrophages Medium Supported Q02880 7155 +ENSG00000077097 TOP2B lung pneumocytes Medium Supported Q02880 7155 +ENSG00000077150 NFKB2 bronchus respiratory epithelial cells Medium Enhanced Q00653 4791 +ENSG00000077150 NFKB2 lung macrophages Medium Enhanced Q00653 4791 +ENSG00000077150 NFKB2 lung pneumocytes Low Enhanced Q00653 4791 +ENSG00000077238 IL4R lung pneumocytes Low Enhanced P24394 3566 +ENSG00000077312 SNRPA bronchus respiratory epithelial cells Medium Enhanced P09012 6626 +ENSG00000077312 SNRPA lung macrophages Medium Enhanced P09012 6626 +ENSG00000077312 SNRPA lung pneumocytes Medium Enhanced P09012 6626 +ENSG00000077327 SPAG6 bronchus respiratory epithelial cells High Enhanced O75602 9576 +ENSG00000077380 DYNC1I2 bronchus respiratory epithelial cells High Enhanced Q13409 1781 +ENSG00000077380 DYNC1I2 lung macrophages Low Enhanced Q13409 1781 +ENSG00000077380 DYNC1I2 lung pneumocytes Medium Enhanced Q13409 1781 +ENSG00000077420 APBB1IP lung macrophages Low Enhanced Q7Z5R6 54518 +ENSG00000077420 APBB1IP lung pneumocytes Low Enhanced Q7Z5R6 54518 +ENSG00000077454 LRCH4 bronchus respiratory epithelial cells Medium Enhanced O75427 4034 +ENSG00000077454 LRCH4 lung macrophages Medium Enhanced O75427 4034 +ENSG00000077454 LRCH4 lung pneumocytes Low Enhanced O75427 4034 +ENSG00000077463 SIRT6 bronchus respiratory epithelial cells High Supported Q8N6T7 51548 +ENSG00000077463 SIRT6 lung macrophages High Supported Q8N6T7 51548 +ENSG00000077463 SIRT6 lung pneumocytes High Supported Q8N6T7 51548 +ENSG00000077514 POLD3 bronchus respiratory epithelial cells High Enhanced Q15054 10714 +ENSG00000077514 POLD3 lung macrophages Medium Enhanced Q15054 10714 +ENSG00000077514 POLD3 lung pneumocytes Low Enhanced Q15054 10714 +ENSG00000077942 FBLN1 bronchus respiratory epithelial cells Medium Enhanced P23142 2192 +ENSG00000078043 PIAS2 lung macrophages Low Enhanced O75928 9063 +ENSG00000078043 PIAS2 lung pneumocytes Low Enhanced O75928 9063 +ENSG00000078081 LAMP3 lung pneumocytes High Enhanced Q9UQV4 27074 +ENSG00000078140 UBE2K bronchus respiratory epithelial cells Medium Supported P61086 3093 +ENSG00000078140 UBE2K lung macrophages Medium Supported P61086 3093 +ENSG00000078140 UBE2K lung pneumocytes Medium Supported P61086 3093 +ENSG00000078369 GNB1 bronchus respiratory epithelial cells Low Supported P62873 2782 +ENSG00000078369 GNB1 lung macrophages Low Supported P62873 2782 +ENSG00000078369 GNB1 lung pneumocytes Low Supported P62873 2782 +ENSG00000078549 ADCYAP1R1 bronchus respiratory epithelial cells Low Enhanced P41586 117 +ENSG00000078549 ADCYAP1R1 lung macrophages Low Enhanced P41586 117 +ENSG00000078674 PCM1 bronchus respiratory epithelial cells Medium Enhanced Q15154 5108 +ENSG00000078674 PCM1 lung pneumocytes Low Enhanced Q15154 5108 +ENSG00000078699 CBFA2T2 bronchus respiratory epithelial cells High Enhanced O43439 9139 +ENSG00000078699 CBFA2T2 lung macrophages Low Enhanced O43439 9139 +ENSG00000078699 CBFA2T2 lung pneumocytes High Enhanced O43439 9139 +ENSG00000078747 ITCH bronchus respiratory epithelial cells Medium Supported Q96J02 83737 +ENSG00000078747 ITCH lung macrophages Medium Supported Q96J02 83737 +ENSG00000078747 ITCH lung pneumocytes Medium Supported Q96J02 83737 +ENSG00000078808 SDF4 bronchus respiratory epithelial cells Medium Enhanced Q9BRK5 51150 +ENSG00000078900 TP73 bronchus respiratory epithelial cells High Enhanced O15350 7161 +ENSG00000078902 TOLLIP bronchus respiratory epithelial cells Medium Enhanced Q9H0E2 54472 +ENSG00000078902 TOLLIP lung macrophages Medium Enhanced Q9H0E2 54472 +ENSG00000079134 THOC1 bronchus respiratory epithelial cells Low Enhanced Q96FV9 9984 +ENSG00000079134 THOC1 lung macrophages Medium Enhanced Q96FV9 9984 +ENSG00000079246 XRCC5 bronchus respiratory epithelial cells Medium Supported P13010 7520 +ENSG00000079246 XRCC5 lung macrophages High Supported P13010 7520 +ENSG00000079246 XRCC5 lung pneumocytes High Supported P13010 7520 +ENSG00000079263 SP140 lung macrophages Low Enhanced Q13342 11262 +ENSG00000079332 SAR1A bronchus respiratory epithelial cells Medium Supported Q9NR31 56681 +ENSG00000079332 SAR1A lung macrophages High Supported Q9NR31 56681 +ENSG00000079332 SAR1A lung pneumocytes Medium Supported Q9NR31 56681 +ENSG00000079691 CARMIL1 bronchus respiratory epithelial cells Medium Enhanced Q5VZK9 55604 +ENSG00000079691 CARMIL1 lung macrophages Low Enhanced Q5VZK9 55604 +ENSG00000079691 CARMIL1 lung pneumocytes Low Enhanced Q5VZK9 55604 +ENSG00000079785 DDX1 lung macrophages High Enhanced Q92499 1653 +ENSG00000079785 DDX1 lung pneumocytes High Enhanced Q92499 1653 +ENSG00000079805 DNM2 bronchus respiratory epithelial cells Medium Enhanced P50570 1785 +ENSG00000079805 DNM2 lung macrophages Low Enhanced P50570 1785 +ENSG00000079819 EPB41L2 bronchus respiratory epithelial cells Medium Supported O43491 2037 +ENSG00000079819 EPB41L2 lung macrophages Low Supported O43491 2037 +ENSG00000079819 EPB41L2 lung pneumocytes High Supported O43491 2037 +ENSG00000079950 STX7 bronchus respiratory epithelial cells Low Enhanced O15400 8417 +ENSG00000079950 STX7 lung macrophages Medium Enhanced O15400 8417 +ENSG00000080298 RFX3 bronchus respiratory epithelial cells Medium Enhanced P48380 5991 +ENSG00000080345 RIF1 bronchus respiratory epithelial cells Medium Supported Q5UIP0 55183 +ENSG00000080345 RIF1 lung macrophages Medium Supported Q5UIP0 55183 +ENSG00000080345 RIF1 lung pneumocytes Medium Supported Q5UIP0 55183 +ENSG00000080503 SMARCA2 bronchus respiratory epithelial cells Medium Enhanced P51531 6595 +ENSG00000080503 SMARCA2 lung macrophages Medium Enhanced P51531 6595 +ENSG00000080503 SMARCA2 lung pneumocytes Medium Enhanced P51531 6595 +ENSG00000080572 PIH1D3 bronchus respiratory epithelial cells High Enhanced Q9NQM4 139212 +ENSG00000080839 RBL1 bronchus respiratory epithelial cells Medium Enhanced P28749 5933 +ENSG00000080839 RBL1 lung macrophages Medium Enhanced P28749 5933 +ENSG00000080839 RBL1 lung pneumocytes Medium Enhanced P28749 5933 +ENSG00000081154 PCNP bronchus respiratory epithelial cells High Supported Q8WW12 57092 +ENSG00000081154 PCNP lung macrophages High Supported Q8WW12 57092 +ENSG00000081154 PCNP lung pneumocytes High Supported Q8WW12 57092 +ENSG00000081181 ARG2 bronchus respiratory epithelial cells Low Enhanced P78540 384 +ENSG00000081189 MEF2C bronchus respiratory epithelial cells Low Enhanced Q06413 4208 +ENSG00000081320 STK17B bronchus respiratory epithelial cells Low Enhanced O94768 9262 +ENSG00000081923 ATP8B1 bronchus respiratory epithelial cells Medium Enhanced O43520 5205 +ENSG00000081923 ATP8B1 lung macrophages Medium Enhanced O43520 5205 +ENSG00000082212 ME2 bronchus respiratory epithelial cells High Enhanced P23368 4200 +ENSG00000082212 ME2 lung macrophages High Enhanced P23368 4200 +ENSG00000082212 ME2 lung pneumocytes Low Enhanced P23368 4200 +ENSG00000082258 CCNT2 bronchus respiratory epithelial cells High Supported O60583 905 +ENSG00000082258 CCNT2 lung macrophages High Supported O60583 905 +ENSG00000082258 CCNT2 lung pneumocytes High Supported O60583 905 +ENSG00000082438 COBLL1 bronchus respiratory epithelial cells Low Enhanced Q53SF7 22837 +ENSG00000082438 COBLL1 lung macrophages Medium Enhanced Q53SF7 22837 +ENSG00000082438 COBLL1 lung pneumocytes Low Enhanced Q53SF7 22837 +ENSG00000082512 TRAF5 bronchus respiratory epithelial cells Low Enhanced O00463 7188 +ENSG00000082512 TRAF5 lung macrophages Low Enhanced O00463 7188 +ENSG00000082512 TRAF5 lung pneumocytes Low Enhanced O00463 7188 +ENSG00000082898 XPO1 bronchus respiratory epithelial cells High Supported O14980 7514 +ENSG00000082898 XPO1 lung macrophages Medium Supported O14980 7514 +ENSG00000082898 XPO1 lung pneumocytes High Supported O14980 7514 +ENSG00000083097 DOPEY1 bronchus respiratory epithelial cells Medium Enhanced Q5JWR5 23033 +ENSG00000083097 DOPEY1 lung macrophages Low Enhanced Q5JWR5 23033 +ENSG00000083168 KAT6A bronchus respiratory epithelial cells Medium Supported Q92794 7994 +ENSG00000083168 KAT6A lung macrophages Low Supported Q92794 7994 +ENSG00000083168 KAT6A lung pneumocytes Medium Supported Q92794 7994 +ENSG00000083642 PDS5B bronchus respiratory epithelial cells High Supported Q9NTI5 23047 +ENSG00000083642 PDS5B lung macrophages Medium Supported Q9NTI5 23047 +ENSG00000083642 PDS5B lung pneumocytes High Supported Q9NTI5 23047 +ENSG00000083720 OXCT1 bronchus respiratory epithelial cells High Enhanced P55809 5019 +ENSG00000083845 RPS5 bronchus respiratory epithelial cells Medium Enhanced P46782 6193 +ENSG00000083845 RPS5 lung macrophages Medium Enhanced P46782 6193 +ENSG00000083845 RPS5 lung pneumocytes Low Enhanced P46782 6193 +ENSG00000083896 YTHDC1 bronchus respiratory epithelial cells High Supported NA NA +ENSG00000083896 YTHDC1 lung macrophages Medium Supported NA NA +ENSG00000083896 YTHDC1 lung pneumocytes Medium Supported NA NA +ENSG00000084090 STARD7 bronchus respiratory epithelial cells Medium Supported Q9NQZ5 56910 +ENSG00000084090 STARD7 lung macrophages Medium Supported Q9NQZ5 56910 +ENSG00000084090 STARD7 lung pneumocytes Medium Supported Q9NQZ5 56910 +ENSG00000084093 REST bronchus respiratory epithelial cells High Supported Q13127 5978 +ENSG00000084093 REST lung macrophages Low Supported Q13127 5978 +ENSG00000084093 REST lung pneumocytes Medium Supported Q13127 5978 +ENSG00000084110 HAL bronchus respiratory epithelial cells Medium Enhanced P42357 3034 +ENSG00000084110 HAL lung macrophages Medium Enhanced P42357 3034 +ENSG00000084110 HAL lung pneumocytes Medium Enhanced P42357 3034 +ENSG00000084207 GSTP1 bronchus respiratory epithelial cells High Enhanced P09211 2950 +ENSG00000084207 GSTP1 lung pneumocytes High Enhanced P09211 2950 +ENSG00000084623 EIF3I bronchus respiratory epithelial cells Medium Enhanced Q13347 8668 +ENSG00000084623 EIF3I lung macrophages Medium Enhanced Q13347 8668 +ENSG00000084623 EIF3I lung pneumocytes Medium Enhanced Q13347 8668 +ENSG00000084652 TXLNA bronchus respiratory epithelial cells High Enhanced P40222 200081 +ENSG00000084652 TXLNA lung macrophages High Enhanced P40222 200081 +ENSG00000084652 TXLNA lung pneumocytes Medium Enhanced P40222 200081 +ENSG00000084676 NCOA1 bronchus respiratory epithelial cells High Enhanced Q15788 8648 +ENSG00000084676 NCOA1 lung macrophages Low Enhanced Q15788 8648 +ENSG00000084676 NCOA1 lung pneumocytes Medium Enhanced Q15788 8648 +ENSG00000084774 CAD bronchus respiratory epithelial cells Medium Supported P27708 790 +ENSG00000084774 CAD lung macrophages Medium Supported P27708 790 +ENSG00000085063 CD59 bronchus respiratory epithelial cells Medium Supported P13987 966 +ENSG00000085063 CD59 lung macrophages Low Supported P13987 966 +ENSG00000085224 ATRX bronchus respiratory epithelial cells High Supported P46100 546 +ENSG00000085224 ATRX lung macrophages High Supported P46100 546 +ENSG00000085224 ATRX lung pneumocytes High Supported P46100 546 +ENSG00000085231 AK6 bronchus respiratory epithelial cells High Supported NA NA +ENSG00000085231 AK6 lung macrophages High Supported NA NA +ENSG00000085231 AK6 lung pneumocytes High Supported NA NA +ENSG00000085265 FCN1 lung macrophages Low Enhanced O00602 2219 +ENSG00000085276 MECOM bronchus respiratory epithelial cells High Supported Q03112 2122 +ENSG00000085276 MECOM lung macrophages High Supported Q03112 2122 +ENSG00000085276 MECOM lung pneumocytes High Supported Q03112 2122 +ENSG00000085377 PREP bronchus respiratory epithelial cells Medium Enhanced P48147 5550 +ENSG00000085377 PREP lung macrophages Medium Enhanced P48147 5550 +ENSG00000085377 PREP lung pneumocytes Medium Enhanced P48147 5550 +ENSG00000085491 SLC25A24 bronchus respiratory epithelial cells High Enhanced NA NA +ENSG00000085491 SLC25A24 lung macrophages High Enhanced NA NA +ENSG00000085491 SLC25A24 lung pneumocytes Low Enhanced NA NA +ENSG00000085721 RRN3 bronchus respiratory epithelial cells High Supported NA NA +ENSG00000085721 RRN3 lung macrophages Low Supported NA NA +ENSG00000085733 CTTN bronchus respiratory epithelial cells High Supported Q14247 2017 +ENSG00000085733 CTTN lung pneumocytes Medium Supported Q14247 2017 +ENSG00000085788 DDHD2 bronchus respiratory epithelial cells Medium Supported O94830 23259 +ENSG00000085788 DDHD2 lung macrophages Low Supported O94830 23259 +ENSG00000085788 DDHD2 lung pneumocytes Low Supported O94830 23259 +ENSG00000085978 ATG16L1 bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000085978 ATG16L1 lung macrophages Medium Enhanced NA NA +ENSG00000085978 ATG16L1 lung pneumocytes Medium Enhanced NA NA +ENSG00000086062 B4GALT1 bronchus respiratory epithelial cells High Enhanced P15291 2683 +ENSG00000086062 B4GALT1 lung macrophages Medium Enhanced P15291 2683 +ENSG00000086062 B4GALT1 lung pneumocytes Medium Enhanced P15291 2683 +ENSG00000086065 CHMP5 bronchus respiratory epithelial cells Low Enhanced Q9NZZ3 51510 +ENSG00000086475 SEPHS1 bronchus respiratory epithelial cells High Enhanced P49903 22929 +ENSG00000086475 SEPHS1 lung macrophages Medium Enhanced P49903 22929 +ENSG00000086475 SEPHS1 lung pneumocytes Medium Enhanced P49903 22929 +ENSG00000086504 MRPL28 bronchus respiratory epithelial cells High Enhanced Q13084 10573 +ENSG00000086504 MRPL28 lung macrophages Medium Enhanced Q13084 10573 +ENSG00000086504 MRPL28 lung pneumocytes Medium Enhanced Q13084 10573 +ENSG00000086548 CEACAM6 bronchus respiratory epithelial cells Low Enhanced P40199 4680 +ENSG00000086548 CEACAM6 lung macrophages Medium Enhanced P40199 4680 +ENSG00000086548 CEACAM6 lung pneumocytes Low Enhanced P40199 4680 +ENSG00000086589 RBM22 bronchus respiratory epithelial cells High Supported Q9NW64 55696 +ENSG00000086589 RBM22 lung macrophages Medium Supported Q9NW64 55696 +ENSG00000086589 RBM22 lung pneumocytes Medium Supported Q9NW64 55696 +ENSG00000086712 TXLNG bronchus respiratory epithelial cells Medium Enhanced Q9NUQ3 55787 +ENSG00000086730 LAT2 lung macrophages Low Enhanced Q9GZY6 7462 +ENSG00000086827 ZW10 bronchus respiratory epithelial cells High Enhanced O43264 9183 +ENSG00000086827 ZW10 lung macrophages High Enhanced O43264 9183 +ENSG00000086827 ZW10 lung pneumocytes High Enhanced O43264 9183 +ENSG00000087086 FTL bronchus respiratory epithelial cells Medium Enhanced P02792 2512 +ENSG00000087086 FTL lung macrophages High Enhanced P02792 2512 +ENSG00000087087 SRRT bronchus respiratory epithelial cells High Supported Q9BXP5 51593 +ENSG00000087087 SRRT lung macrophages Medium Supported Q9BXP5 51593 +ENSG00000087087 SRRT lung pneumocytes Medium Supported Q9BXP5 51593 +ENSG00000087152 ATXN7L3 bronchus respiratory epithelial cells High Supported Q14CW9 56970 +ENSG00000087152 ATXN7L3 lung macrophages High Supported Q14CW9 56970 +ENSG00000087152 ATXN7L3 lung pneumocytes High Supported Q14CW9 56970 +ENSG00000087191 PSMC5 bronchus respiratory epithelial cells High Enhanced P62195 5705 +ENSG00000087191 PSMC5 lung macrophages Low Enhanced P62195 5705 +ENSG00000087191 PSMC5 lung pneumocytes Medium Enhanced P62195 5705 +ENSG00000087206 UIMC1 lung macrophages Medium Enhanced Q96RL1 51720 +ENSG00000087253 LPCAT2 lung macrophages Medium Enhanced Q7L5N7 54947 +ENSG00000087253 LPCAT2 lung pneumocytes Medium Enhanced Q7L5N7 54947 +ENSG00000087274 ADD1 bronchus respiratory epithelial cells Medium Enhanced P35611 118 +ENSG00000087274 ADD1 lung macrophages Low Enhanced P35611 118 +ENSG00000087274 ADD1 lung pneumocytes Low Enhanced P35611 118 +ENSG00000087302 C14orf166 bronchus respiratory epithelial cells High Supported Q9Y224 51637 +ENSG00000087302 C14orf166 lung macrophages Medium Supported Q9Y224 51637 +ENSG00000087302 C14orf166 lung pneumocytes Medium Supported Q9Y224 51637 +ENSG00000087303 NID2 bronchus respiratory epithelial cells Low Enhanced Q14112 22795 +ENSG00000087303 NID2 lung macrophages Medium Enhanced Q14112 22795 +ENSG00000087303 NID2 lung pneumocytes Medium Enhanced Q14112 22795 +ENSG00000087365 SF3B2 bronchus respiratory epithelial cells High Supported Q13435 10992 +ENSG00000087365 SF3B2 lung macrophages High Supported Q13435 10992 +ENSG00000087365 SF3B2 lung pneumocytes High Supported Q13435 10992 +ENSG00000087470 DNM1L lung macrophages Medium Enhanced O00429 10059 +ENSG00000087470 DNM1L lung pneumocytes Low Enhanced O00429 10059 +ENSG00000087842 PIR bronchus respiratory epithelial cells Medium Enhanced O00625 8544 +ENSG00000087842 PIR lung macrophages Low Enhanced O00625 8544 +ENSG00000087842 PIR lung pneumocytes Medium Enhanced O00625 8544 +ENSG00000087884 AAMDC bronchus respiratory epithelial cells Medium Enhanced Q9H7C9 28971 +ENSG00000087903 RFX2 bronchus respiratory epithelial cells Medium Enhanced P48378 5990 +ENSG00000088247 KHSRP bronchus respiratory epithelial cells Medium Enhanced Q92945 8570 +ENSG00000088247 KHSRP lung pneumocytes Medium Enhanced Q92945 8570 +ENSG00000088305 DNMT3B bronchus respiratory epithelial cells Medium Enhanced Q9UBC3 1789 +ENSG00000088305 DNMT3B lung macrophages Medium Enhanced Q9UBC3 1789 +ENSG00000088305 DNMT3B lung pneumocytes Low Enhanced Q9UBC3 1789 +ENSG00000088325 TPX2 bronchus respiratory epithelial cells Medium Enhanced Q9ULW0 22974 +ENSG00000088325 TPX2 lung macrophages Medium Enhanced Q9ULW0 22974 +ENSG00000088325 TPX2 lung pneumocytes Low Enhanced Q9ULW0 22974 +ENSG00000088367 EPB41L1 bronchus respiratory epithelial cells High Enhanced Q9H4G0 2036 +ENSG00000088367 EPB41L1 lung macrophages Low Enhanced Q9H4G0 2036 +ENSG00000088367 EPB41L1 lung pneumocytes Low Enhanced Q9H4G0 2036 +ENSG00000088682 COQ9 bronchus respiratory epithelial cells High Supported O75208 57017 +ENSG00000088682 COQ9 lung macrophages High Supported O75208 57017 +ENSG00000088756 ARHGAP28 lung macrophages Low Enhanced Q9P2N2 NA +ENSG00000088827 SIGLEC1 lung macrophages High Supported Q9BZZ2 6614 +ENSG00000088833 NSFL1C bronchus respiratory epithelial cells Medium Enhanced Q9UNZ2 55968 +ENSG00000088888 MAVS bronchus respiratory epithelial cells High Enhanced Q7Z434 57506 +ENSG00000088888 MAVS lung macrophages High Enhanced Q7Z434 57506 +ENSG00000088888 MAVS lung pneumocytes High Enhanced Q7Z434 57506 +ENSG00000088930 XRN2 lung macrophages High Supported Q9H0D6 22803 +ENSG00000088930 XRN2 lung pneumocytes High Supported Q9H0D6 22803 +ENSG00000088992 TESC bronchus respiratory epithelial cells Medium Enhanced Q96BS2 54997 +ENSG00000088992 TESC lung pneumocytes Low Enhanced Q96BS2 54997 +ENSG00000089022 MAPKAPK5 bronchus respiratory epithelial cells Medium Supported Q8IW41 8550 +ENSG00000089022 MAPKAPK5 lung macrophages Medium Supported Q8IW41 8550 +ENSG00000089022 MAPKAPK5 lung pneumocytes Medium Supported Q8IW41 8550 +ENSG00000089048 ESF1 bronchus respiratory epithelial cells High Supported Q9H501 51575 +ENSG00000089048 ESF1 lung macrophages Medium Supported Q9H501 51575 +ENSG00000089048 ESF1 lung pneumocytes Medium Supported Q9H501 51575 +ENSG00000089053 ANAPC5 bronchus respiratory epithelial cells High Supported Q9UJX4 51433 +ENSG00000089053 ANAPC5 lung macrophages High Supported Q9UJX4 51433 +ENSG00000089053 ANAPC5 lung pneumocytes High Supported Q9UJX4 51433 +ENSG00000089154 GCN1 bronchus respiratory epithelial cells Medium Enhanced Q92616 10985 +ENSG00000089154 GCN1 lung macrophages Medium Enhanced Q92616 10985 +ENSG00000089159 PXN bronchus respiratory epithelial cells Medium Enhanced P49023 5829 +ENSG00000089159 PXN lung pneumocytes High Enhanced P49023 5829 +ENSG00000089163 SIRT4 bronchus respiratory epithelial cells Low Enhanced Q9Y6E7 23409 +ENSG00000089163 SIRT4 lung macrophages Low Enhanced Q9Y6E7 23409 +ENSG00000089163 SIRT4 lung pneumocytes Low Enhanced Q9Y6E7 23409 +ENSG00000089220 PEBP1 bronchus respiratory epithelial cells Low Enhanced P30086 5037 +ENSG00000089220 PEBP1 lung macrophages Low Enhanced P30086 5037 +ENSG00000089248 ERP29 bronchus respiratory epithelial cells High Enhanced P30040 10961 +ENSG00000089248 ERP29 lung macrophages High Enhanced P30040 10961 +ENSG00000089248 ERP29 lung pneumocytes Medium Enhanced P30040 10961 +ENSG00000089280 FUS bronchus respiratory epithelial cells High Enhanced P35637 2521 +ENSG00000089280 FUS lung macrophages High Enhanced P35637 2521 +ENSG00000089280 FUS lung pneumocytes High Enhanced P35637 2521 +ENSG00000089356 FXYD3 bronchus respiratory epithelial cells Medium Enhanced Q14802 5349 +ENSG00000089356 FXYD3 lung macrophages Medium Enhanced Q14802 5349 +ENSG00000089356 FXYD3 lung pneumocytes Low Enhanced Q14802 5349 +ENSG00000089597 GANAB bronchus respiratory epithelial cells Medium Enhanced Q14697 23193 +ENSG00000089597 GANAB lung macrophages Medium Enhanced Q14697 23193 +ENSG00000089597 GANAB lung pneumocytes Low Enhanced Q14697 23193 +ENSG00000089639 GMIP bronchus respiratory epithelial cells Medium Enhanced Q9P107 51291 +ENSG00000089639 GMIP lung macrophages Medium Enhanced Q9P107 51291 +ENSG00000089639 GMIP lung pneumocytes Low Enhanced Q9P107 51291 +ENSG00000089693 MLF2 bronchus respiratory epithelial cells High Enhanced Q15773 8079 +ENSG00000089693 MLF2 lung macrophages High Enhanced Q15773 8079 +ENSG00000089693 MLF2 lung pneumocytes Low Enhanced Q15773 8079 +ENSG00000089820 ARHGAP4 bronchus respiratory epithelial cells Low Enhanced P98171 393 +ENSG00000089820 ARHGAP4 lung macrophages Medium Enhanced P98171 393 +ENSG00000089902 RCOR1 bronchus respiratory epithelial cells High Supported Q9UKL0 23186 +ENSG00000089902 RCOR1 lung macrophages High Supported Q9UKL0 23186 +ENSG00000089902 RCOR1 lung pneumocytes High Supported Q9UKL0 23186 +ENSG00000090013 BLVRB bronchus respiratory epithelial cells High Enhanced P30043 645 +ENSG00000090013 BLVRB lung macrophages Medium Enhanced P30043 645 +ENSG00000090020 SLC9A1 bronchus respiratory epithelial cells Medium Enhanced P19634 6548 +ENSG00000090054 SPTLC1 bronchus respiratory epithelial cells Medium Supported O15269 10558 +ENSG00000090054 SPTLC1 lung macrophages Medium Supported O15269 10558 +ENSG00000090054 SPTLC1 lung pneumocytes Medium Supported O15269 10558 +ENSG00000090060 PAPOLA bronchus respiratory epithelial cells Medium Supported P51003 10914 +ENSG00000090060 PAPOLA lung macrophages Medium Supported P51003 10914 +ENSG00000090060 PAPOLA lung pneumocytes Medium Supported P51003 10914 +ENSG00000090061 CCNK bronchus respiratory epithelial cells Medium Enhanced O75909 8812 +ENSG00000090061 CCNK lung macrophages Low Enhanced O75909 8812 +ENSG00000090061 CCNK lung pneumocytes Low Enhanced O75909 8812 +ENSG00000090273 NUDC bronchus respiratory epithelial cells Medium Enhanced Q9Y266 10726 +ENSG00000090273 NUDC lung macrophages Low Enhanced Q9Y266 10726 +ENSG00000090339 ICAM1 lung macrophages Medium Enhanced P05362 3383 +ENSG00000090339 ICAM1 lung pneumocytes High Enhanced P05362 3383 +ENSG00000090372 STRN4 bronchus respiratory epithelial cells Medium Enhanced Q9NRL3 29888 +ENSG00000090372 STRN4 lung macrophages Low Enhanced Q9NRL3 29888 +ENSG00000090372 STRN4 lung pneumocytes Medium Enhanced Q9NRL3 29888 +ENSG00000090382 LYZ bronchus respiratory epithelial cells Low Enhanced P61626 4069 +ENSG00000090382 LYZ lung macrophages High Enhanced P61626 4069 +ENSG00000090447 TFAP4 bronchus respiratory epithelial cells Low Supported Q01664 7023 +ENSG00000090447 TFAP4 lung macrophages Low Supported Q01664 7023 +ENSG00000090447 TFAP4 lung pneumocytes Low Supported Q01664 7023 +ENSG00000090512 FETUB bronchus respiratory epithelial cells Medium Supported Q9UGM5 26998 +ENSG00000090512 FETUB lung macrophages Medium Supported Q9UGM5 26998 +ENSG00000090512 FETUB lung pneumocytes Low Supported Q9UGM5 26998 +ENSG00000090520 DNAJB11 bronchus respiratory epithelial cells Medium Supported Q9UBS4 51726 +ENSG00000090520 DNAJB11 lung macrophages High Supported Q9UBS4 51726 +ENSG00000090520 DNAJB11 lung pneumocytes Medium Supported Q9UBS4 51726 +ENSG00000090615 GOLGA3 bronchus respiratory epithelial cells Medium Enhanced Q08378 2802 +ENSG00000090615 GOLGA3 lung macrophages Low Enhanced Q08378 2802 +ENSG00000090615 GOLGA3 lung pneumocytes Low Enhanced Q08378 2802 +ENSG00000090659 CD209 lung macrophages Medium Supported Q9NNX6 30835 +ENSG00000090861 AARS bronchus respiratory epithelial cells Medium Supported P49588 16 +ENSG00000090861 AARS lung macrophages Medium Supported P49588 16 +ENSG00000090861 AARS lung pneumocytes Low Supported P49588 16 +ENSG00000090863 GLG1 bronchus respiratory epithelial cells High Supported Q92896 2734 +ENSG00000090863 GLG1 lung macrophages High Supported Q92896 2734 +ENSG00000090863 GLG1 lung pneumocytes Low Supported Q92896 2734 +ENSG00000091136 LAMB1 bronchus respiratory epithelial cells Low Enhanced P07942 3912 +ENSG00000091136 LAMB1 lung pneumocytes Medium Enhanced P07942 3912 +ENSG00000091140 DLD bronchus respiratory epithelial cells High Enhanced P09622 1738 +ENSG00000091140 DLD lung macrophages Medium Enhanced P09622 1738 +ENSG00000091140 DLD lung pneumocytes Medium Enhanced P09622 1738 +ENSG00000091164 TXNL1 bronchus respiratory epithelial cells Medium Supported O43396 9352 +ENSG00000091164 TXNL1 lung macrophages Medium Supported O43396 9352 +ENSG00000091164 TXNL1 lung pneumocytes Low Supported O43396 9352 +ENSG00000091409 ITGA6 lung macrophages Low Enhanced P23229 3655 +ENSG00000091483 FH bronchus respiratory epithelial cells Medium Enhanced P07954 2271 +ENSG00000091483 FH lung macrophages Medium Enhanced P07954 2271 +ENSG00000091483 FH lung pneumocytes Low Enhanced P07954 2271 +ENSG00000091527 CDV3 bronchus respiratory epithelial cells Medium Enhanced Q9UKY7 55573 +ENSG00000091527 CDV3 lung macrophages Low Enhanced Q9UKY7 55573 +ENSG00000091527 CDV3 lung pneumocytes Medium Enhanced Q9UKY7 55573 +ENSG00000091592 NLRP1 lung macrophages Medium Enhanced Q9C000 22861 +ENSG00000091651 ORC6 lung macrophages Low Enhanced Q9Y5N6 23594 +ENSG00000091732 ZC3HC1 bronchus respiratory epithelial cells Medium Enhanced Q86WB0 51530 +ENSG00000091732 ZC3HC1 lung macrophages Medium Enhanced Q86WB0 51530 +ENSG00000091732 ZC3HC1 lung pneumocytes Medium Enhanced Q86WB0 51530 +ENSG00000092199 HNRNPC bronchus respiratory epithelial cells High Supported P07910 3183 +ENSG00000092199 HNRNPC lung macrophages High Supported P07910 3183 +ENSG00000092199 HNRNPC lung pneumocytes High Supported P07910 3183 +ENSG00000092200 RPGRIP1 bronchus respiratory epithelial cells Low Enhanced Q96KN7 57096 +ENSG00000092201 SUPT16H bronchus respiratory epithelial cells Medium Enhanced Q9Y5B9 11198 +ENSG00000092201 SUPT16H lung macrophages Low Enhanced Q9Y5B9 11198 +ENSG00000092201 SUPT16H lung pneumocytes Low Enhanced Q9Y5B9 11198 +ENSG00000092208 GEMIN2 bronchus respiratory epithelial cells Low Enhanced O14893 8487 +ENSG00000092208 GEMIN2 lung macrophages Medium Enhanced O14893 8487 +ENSG00000092208 GEMIN2 lung pneumocytes Medium Enhanced O14893 8487 +ENSG00000092439 TRPM7 bronchus respiratory epithelial cells Low Enhanced Q96QT4 54822 +ENSG00000092529 CAPN3 lung macrophages Low Enhanced P20807 825 +ENSG00000092621 PHGDH bronchus respiratory epithelial cells High Enhanced O43175 26227 +ENSG00000092621 PHGDH lung macrophages Low Enhanced O43175 26227 +ENSG00000092621 PHGDH lung pneumocytes Low Enhanced O43175 26227 +ENSG00000092820 EZR bronchus respiratory epithelial cells High Enhanced P15311 7430 +ENSG00000092820 EZR lung macrophages Low Enhanced P15311 7430 +ENSG00000092820 EZR lung pneumocytes Medium Enhanced P15311 7430 +ENSG00000092964 DPYSL2 lung macrophages High Supported Q16555 1808 +ENSG00000092964 DPYSL2 lung pneumocytes Medium Supported Q16555 1808 +ENSG00000093000 NUP50 bronchus respiratory epithelial cells High Enhanced Q9UKX7 10762 +ENSG00000093000 NUP50 lung macrophages High Enhanced Q9UKX7 10762 +ENSG00000093000 NUP50 lung pneumocytes High Enhanced Q9UKX7 10762 +ENSG00000093009 CDC45 bronchus respiratory epithelial cells Low Enhanced O75419 8318 +ENSG00000093009 CDC45 lung macrophages Low Enhanced O75419 8318 +ENSG00000093009 CDC45 lung pneumocytes Low Enhanced O75419 8318 +ENSG00000093010 COMT bronchus respiratory epithelial cells Medium Enhanced P21964 1312 +ENSG00000093010 COMT lung macrophages Medium Enhanced P21964 1312 +ENSG00000093010 COMT lung pneumocytes Low Enhanced P21964 1312 +ENSG00000094916 CBX5 bronchus respiratory epithelial cells Medium Enhanced P45973 23468 +ENSG00000094916 CBX5 lung pneumocytes Low Enhanced P45973 23468 +ENSG00000095002 MSH2 bronchus respiratory epithelial cells Medium Supported P43246 4436 +ENSG00000095002 MSH2 lung macrophages Medium Supported P43246 4436 +ENSG00000095002 MSH2 lung pneumocytes Medium Supported P43246 4436 +ENSG00000095303 PTGS1 lung macrophages Low Enhanced P23219 5742 +ENSG00000095321 CRAT bronchus respiratory epithelial cells Medium Enhanced P43155 1384 +ENSG00000095321 CRAT lung macrophages Low Enhanced P43155 1384 +ENSG00000095637 SORBS1 bronchus respiratory epithelial cells Medium Enhanced Q9BX66 10580 +ENSG00000095637 SORBS1 lung macrophages Medium Enhanced Q9BX66 10580 +ENSG00000095637 SORBS1 lung pneumocytes Medium Enhanced Q9BX66 10580 +ENSG00000095713 CRTAC1 bronchus respiratory epithelial cells Medium Enhanced Q9NQ79 55118 +ENSG00000095713 CRTAC1 lung macrophages Medium Enhanced Q9NQ79 55118 +ENSG00000095713 CRTAC1 lung pneumocytes Medium Enhanced Q9NQ79 55118 +ENSG00000095794 CREM bronchus respiratory epithelial cells Medium Enhanced Q03060 1390 +ENSG00000095794 CREM lung macrophages Medium Enhanced Q03060 1390 +ENSG00000096060 FKBP5 bronchus respiratory epithelial cells High Enhanced Q13451 2289 +ENSG00000096060 FKBP5 lung macrophages High Enhanced Q13451 2289 +ENSG00000096060 FKBP5 lung pneumocytes High Enhanced Q13451 2289 +ENSG00000096384 HSP90AB1 bronchus respiratory epithelial cells High Enhanced P08238 3326 +ENSG00000096384 HSP90AB1 lung macrophages Medium Enhanced P08238 3326 +ENSG00000096384 HSP90AB1 lung pneumocytes Medium Enhanced P08238 3326 +ENSG00000096401 CDC5L bronchus respiratory epithelial cells High Supported Q99459 988 +ENSG00000096401 CDC5L lung macrophages Medium Supported Q99459 988 +ENSG00000096401 CDC5L lung pneumocytes Medium Supported Q99459 988 +ENSG00000096696 DSP bronchus respiratory epithelial cells Medium Enhanced P15924 1832 +ENSG00000097007 ABL1 bronchus respiratory epithelial cells Medium Supported P00519 25 +ENSG00000097007 ABL1 lung macrophages Low Supported P00519 25 +ENSG00000097007 ABL1 lung pneumocytes Medium Supported P00519 25 +ENSG00000097021 ACOT7 bronchus respiratory epithelial cells Medium Enhanced O00154 11332 +ENSG00000097021 ACOT7 lung macrophages Low Enhanced O00154 11332 +ENSG00000097033 SH3GLB1 bronchus respiratory epithelial cells Medium Enhanced Q9Y371 51100 +ENSG00000097033 SH3GLB1 lung macrophages Medium Enhanced Q9Y371 51100 +ENSG00000097046 CDC7 bronchus respiratory epithelial cells Medium Enhanced O00311 8317 +ENSG00000097046 CDC7 lung macrophages Low Enhanced O00311 8317 +ENSG00000099139 PCSK5 lung macrophages Medium Enhanced Q92824 5125 +ENSG00000099260 PALMD bronchus respiratory epithelial cells High Supported Q9NP74 54873 +ENSG00000099260 PALMD lung macrophages Medium Supported Q9NP74 54873 +ENSG00000099260 PALMD lung pneumocytes Medium Supported Q9NP74 54873 +ENSG00000099284 H2AFY2 bronchus respiratory epithelial cells Medium Enhanced Q9P0M6 55506 +ENSG00000099284 H2AFY2 lung macrophages Medium Enhanced Q9P0M6 55506 +ENSG00000099284 H2AFY2 lung pneumocytes Medium Enhanced Q9P0M6 55506 +ENSG00000099290 WASHC2A bronchus respiratory epithelial cells Medium Supported Q641Q2 387680 +ENSG00000099290 WASHC2A lung macrophages Medium Supported Q641Q2 387680 +ENSG00000099290 WASHC2A lung pneumocytes Low Supported Q641Q2 387680 +ENSG00000099341 PSMD8 bronchus respiratory epithelial cells Medium Enhanced P48556 5714 +ENSG00000099341 PSMD8 lung macrophages Medium Enhanced P48556 5714 +ENSG00000099381 SETD1A bronchus respiratory epithelial cells High Enhanced O15047 9739 +ENSG00000099381 SETD1A lung macrophages Medium Enhanced O15047 9739 +ENSG00000099381 SETD1A lung pneumocytes Medium Enhanced O15047 9739 +ENSG00000099783 HNRNPM bronchus respiratory epithelial cells High Supported P52272 4670 +ENSG00000099783 HNRNPM lung macrophages High Supported P52272 4670 +ENSG00000099783 HNRNPM lung pneumocytes High Supported P52272 4670 +ENSG00000099797 TECR bronchus respiratory epithelial cells Medium Supported Q9NZ01 9524 +ENSG00000099797 TECR lung macrophages Low Supported Q9NZ01 9524 +ENSG00000099812 MISP bronchus respiratory epithelial cells Low Enhanced Q8IVT2 126353 +ENSG00000099814 CEP170B bronchus respiratory epithelial cells Medium Enhanced Q9Y4F5 283638 +ENSG00000099817 POLR2E bronchus respiratory epithelial cells High Supported P19388 5434 +ENSG00000099817 POLR2E lung macrophages Medium Supported P19388 5434 +ENSG00000099817 POLR2E lung pneumocytes Medium Supported P19388 5434 +ENSG00000099875 MKNK2 bronchus respiratory epithelial cells Medium Enhanced Q9HBH9 2872 +ENSG00000099875 MKNK2 lung macrophages High Enhanced Q9HBH9 2872 +ENSG00000099875 MKNK2 lung pneumocytes High Enhanced Q9HBH9 2872 +ENSG00000099889 ARVCF bronchus respiratory epithelial cells Low Enhanced O00192 421 +ENSG00000099889 ARVCF lung macrophages Low Enhanced O00192 421 +ENSG00000099901 RANBP1 bronchus respiratory epithelial cells Medium Enhanced P43487 5902 +ENSG00000099940 SNAP29 bronchus respiratory epithelial cells Low Supported O95721 9342 +ENSG00000099940 SNAP29 lung macrophages Medium Supported O95721 9342 +ENSG00000099956 SMARCB1 bronchus respiratory epithelial cells High Supported A0A0U1RRB8 NA +ENSG00000099956 SMARCB1 lung macrophages High Supported A0A0U1RRB8 NA +ENSG00000099956 SMARCB1 lung pneumocytes High Supported A0A0U1RRB8 NA +ENSG00000099994 SUSD2 bronchus respiratory epithelial cells Low Enhanced Q9UGT4 56241 +ENSG00000099994 SUSD2 lung macrophages Medium Enhanced Q9UGT4 56241 +ENSG00000099994 SUSD2 lung pneumocytes High Enhanced Q9UGT4 56241 +ENSG00000099995 SF3A1 bronchus respiratory epithelial cells High Enhanced Q15459 10291 +ENSG00000099995 SF3A1 lung macrophages Medium Enhanced Q15459 10291 +ENSG00000099995 SF3A1 lung pneumocytes High Enhanced Q15459 10291 +ENSG00000100023 PPIL2 bronchus respiratory epithelial cells High Supported Q13356 23759 +ENSG00000100023 PPIL2 lung macrophages High Supported Q13356 23759 +ENSG00000100023 PPIL2 lung pneumocytes Medium Supported Q13356 23759 +ENSG00000100024 UPB1 bronchus respiratory epithelial cells Low Enhanced Q9UBR1 51733 +ENSG00000100028 SNRPD3 bronchus respiratory epithelial cells High Supported P62318 6634 +ENSG00000100028 SNRPD3 lung macrophages High Supported P62318 6634 +ENSG00000100028 SNRPD3 lung pneumocytes High Supported P62318 6634 +ENSG00000100029 PES1 bronchus respiratory epithelial cells Low Supported O00541 23481 +ENSG00000100029 PES1 lung macrophages Medium Supported O00541 23481 +ENSG00000100029 PES1 lung pneumocytes Low Supported O00541 23481 +ENSG00000100031 GGT1 bronchus respiratory epithelial cells Low Supported P19440 2678 +ENSG00000100056 DGCR14 bronchus respiratory epithelial cells Medium Enhanced Q96DF8 8220 +ENSG00000100056 DGCR14 lung macrophages Low Enhanced Q96DF8 8220 +ENSG00000100056 DGCR14 lung pneumocytes Medium Enhanced Q96DF8 8220 +ENSG00000100083 GGA1 bronchus respiratory epithelial cells Medium Supported Q9UJY5 26088 +ENSG00000100083 GGA1 lung macrophages Medium Supported Q9UJY5 26088 +ENSG00000100083 GGA1 lung pneumocytes Medium Supported Q9UJY5 26088 +ENSG00000100084 HIRA lung macrophages Medium Enhanced P54198 7290 +ENSG00000100084 HIRA lung pneumocytes Medium Enhanced P54198 7290 +ENSG00000100092 SH3BP1 bronchus respiratory epithelial cells Medium Enhanced Q9Y3L3 23616 +ENSG00000100092 SH3BP1 lung macrophages High Enhanced Q9Y3L3 23616 +ENSG00000100097 LGALS1 lung macrophages Low Enhanced P09382 3956 +ENSG00000100097 LGALS1 lung pneumocytes Low Enhanced P09382 3956 +ENSG00000100106 TRIOBP bronchus respiratory epithelial cells Low Enhanced Q9H2D6 11078 +ENSG00000100106 TRIOBP lung macrophages Medium Enhanced Q9H2D6 11078 +ENSG00000100106 TRIOBP lung pneumocytes Medium Enhanced Q9H2D6 11078 +ENSG00000100142 POLR2F bronchus respiratory epithelial cells High Supported P61218 5435 +ENSG00000100142 POLR2F lung macrophages Medium Supported P61218 5435 +ENSG00000100142 POLR2F lung pneumocytes High Supported P61218 5435 +ENSG00000100162 CENPM lung macrophages Low Enhanced Q9NSP4 79019 +ENSG00000100201 DDX17 bronchus respiratory epithelial cells Medium Enhanced Q92841 10521 +ENSG00000100201 DDX17 lung macrophages Low Enhanced Q92841 10521 +ENSG00000100201 DDX17 lung pneumocytes Medium Enhanced Q92841 10521 +ENSG00000100216 TOMM22 bronchus respiratory epithelial cells High Enhanced Q9NS69 56993 +ENSG00000100216 TOMM22 lung macrophages High Enhanced Q9NS69 56993 +ENSG00000100216 TOMM22 lung pneumocytes High Enhanced Q9NS69 56993 +ENSG00000100220 RTCB bronchus respiratory epithelial cells Medium Enhanced Q9Y3I0 51493 +ENSG00000100220 RTCB lung macrophages Low Enhanced Q9Y3I0 51493 +ENSG00000100220 RTCB lung pneumocytes Low Enhanced Q9Y3I0 51493 +ENSG00000100242 SUN2 bronchus respiratory epithelial cells High Supported Q9UH99 25777 +ENSG00000100242 SUN2 lung macrophages High Supported Q9UH99 25777 +ENSG00000100242 SUN2 lung pneumocytes High Supported Q9UH99 25777 +ENSG00000100266 PACSIN2 bronchus respiratory epithelial cells Medium Enhanced Q9UNF0 11252 +ENSG00000100266 PACSIN2 lung macrophages Medium Enhanced Q9UNF0 11252 +ENSG00000100266 PACSIN2 lung pneumocytes Low Enhanced Q9UNF0 11252 +ENSG00000100292 HMOX1 lung macrophages High Enhanced P09601 3162 +ENSG00000100297 MCM5 bronchus respiratory epithelial cells Medium Enhanced P33992 4174 +ENSG00000100297 MCM5 lung macrophages Medium Enhanced P33992 4174 +ENSG00000100299 ARSA bronchus respiratory epithelial cells Medium Enhanced P15289 410 +ENSG00000100299 ARSA lung macrophages Medium Enhanced P15289 410 +ENSG00000100299 ARSA lung pneumocytes Medium Enhanced P15289 410 +ENSG00000100302 RASD2 bronchus respiratory epithelial cells Medium Enhanced Q96D21 23551 +ENSG00000100302 RASD2 lung macrophages Medium Enhanced Q96D21 23551 +ENSG00000100302 RASD2 lung pneumocytes Low Enhanced Q96D21 23551 +ENSG00000100307 CBX7 bronchus respiratory epithelial cells Medium Enhanced O95931 23492 +ENSG00000100307 CBX7 lung macrophages Low Enhanced O95931 23492 +ENSG00000100307 CBX7 lung pneumocytes Medium Enhanced O95931 23492 +ENSG00000100311 PDGFB bronchus respiratory epithelial cells Medium Supported P01127 5155 +ENSG00000100311 PDGFB lung macrophages Medium Supported P01127 5155 +ENSG00000100311 PDGFB lung pneumocytes Medium Supported P01127 5155 +ENSG00000100320 RBFOX2 bronchus respiratory epithelial cells Low Enhanced B0QYY7 NA +ENSG00000100320 RBFOX2 lung macrophages Medium Enhanced B0QYY7 NA +ENSG00000100320 RBFOX2 lung pneumocytes High Enhanced B0QYY7 NA +ENSG00000100321 SYNGR1 bronchus respiratory epithelial cells Low Enhanced O43759 9145 +ENSG00000100321 SYNGR1 lung macrophages Medium Enhanced O43759 9145 +ENSG00000100321 SYNGR1 lung pneumocytes Low Enhanced O43759 9145 +ENSG00000100342 APOL1 bronchus respiratory epithelial cells Low Supported O14791 8542 +ENSG00000100345 MYH9 bronchus respiratory epithelial cells Low Enhanced P35579 4627 +ENSG00000100345 MYH9 lung macrophages Medium Enhanced P35579 4627 +ENSG00000100345 MYH9 lung pneumocytes High Enhanced P35579 4627 +ENSG00000100347 SAMM50 bronchus respiratory epithelial cells Medium Enhanced Q9Y512 25813 +ENSG00000100347 SAMM50 lung macrophages Medium Enhanced Q9Y512 25813 +ENSG00000100347 SAMM50 lung pneumocytes Medium Enhanced Q9Y512 25813 +ENSG00000100365 NCF4 lung macrophages Medium Enhanced Q15080 4689 +ENSG00000100380 ST13 bronchus respiratory epithelial cells High Enhanced P50502 6767 +ENSG00000100380 ST13 lung macrophages Low Enhanced P50502 6767 +ENSG00000100380 ST13 lung pneumocytes Low Enhanced P50502 6767 +ENSG00000100393 EP300 bronchus respiratory epithelial cells Medium Supported Q09472 2033 +ENSG00000100393 EP300 lung macrophages Medium Supported Q09472 2033 +ENSG00000100393 EP300 lung pneumocytes Medium Supported Q09472 2033 +ENSG00000100401 RANGAP1 bronchus respiratory epithelial cells Medium Enhanced P46060 5905 +ENSG00000100401 RANGAP1 lung macrophages Medium Enhanced P46060 5905 +ENSG00000100401 RANGAP1 lung pneumocytes Medium Enhanced P46060 5905 +ENSG00000100410 PHF5A bronchus respiratory epithelial cells High Supported Q7RTV0 84844 +ENSG00000100410 PHF5A lung macrophages Medium Supported Q7RTV0 84844 +ENSG00000100410 PHF5A lung pneumocytes Medium Supported Q7RTV0 84844 +ENSG00000100412 ACO2 lung macrophages High Enhanced Q99798 50 +ENSG00000100412 ACO2 lung pneumocytes Medium Enhanced Q99798 50 +ENSG00000100429 HDAC10 bronchus respiratory epithelial cells Medium Supported Q969S8 83933 +ENSG00000100429 HDAC10 lung macrophages High Supported Q969S8 83933 +ENSG00000100429 HDAC10 lung pneumocytes High Supported Q969S8 83933 +ENSG00000100442 FKBP3 bronchus respiratory epithelial cells Medium Supported Q00688 2287 +ENSG00000100442 FKBP3 lung macrophages Medium Supported Q00688 2287 +ENSG00000100442 FKBP3 lung pneumocytes Low Supported Q00688 2287 +ENSG00000100503 NIN bronchus respiratory epithelial cells Medium Enhanced Q8N4C6 51199 +ENSG00000100503 NIN lung macrophages Medium Enhanced Q8N4C6 51199 +ENSG00000100504 PYGL lung macrophages Medium Enhanced P06737 5836 +ENSG00000100523 DDHD1 bronchus respiratory epithelial cells Low Enhanced Q8NEL9 80821 +ENSG00000100523 DDHD1 lung macrophages Medium Enhanced Q8NEL9 80821 +ENSG00000100554 ATP6V1D lung macrophages Low Enhanced Q9Y5K8 51382 +ENSG00000100558 PLEK2 bronchus respiratory epithelial cells Low Enhanced Q9NYT0 26499 +ENSG00000100558 PLEK2 lung macrophages High Enhanced Q9NYT0 26499 +ENSG00000100583 SAMD15 bronchus respiratory epithelial cells High Enhanced Q9P1V8 161394 +ENSG00000100583 SAMD15 lung macrophages Medium Enhanced Q9P1V8 161394 +ENSG00000100583 SAMD15 lung pneumocytes Medium Enhanced Q9P1V8 161394 +ENSG00000100591 AHSA1 bronchus respiratory epithelial cells Medium Supported O95433 10598 +ENSG00000100591 AHSA1 lung macrophages Low Supported O95433 10598 +ENSG00000100600 LGMN bronchus respiratory epithelial cells Low Enhanced Q99538 5641 +ENSG00000100600 LGMN lung macrophages Low Enhanced Q99538 5641 +ENSG00000100603 SNW1 bronchus respiratory epithelial cells High Supported Q13573 22938 +ENSG00000100603 SNW1 lung macrophages High Supported Q13573 22938 +ENSG00000100603 SNW1 lung pneumocytes High Supported Q13573 22938 +ENSG00000100604 CHGA bronchus respiratory epithelial cells Low Enhanced NA NA +ENSG00000100644 HIF1A bronchus respiratory epithelial cells Medium Supported Q16665 3091 +ENSG00000100644 HIF1A lung macrophages Medium Supported Q16665 3091 +ENSG00000100644 HIF1A lung pneumocytes Medium Supported Q16665 3091 +ENSG00000100664 EIF5 bronchus respiratory epithelial cells High Supported P55010 1983 +ENSG00000100664 EIF5 lung macrophages High Supported P55010 1983 +ENSG00000100664 EIF5 lung pneumocytes Medium Supported P55010 1983 +ENSG00000100722 ZC3H14 bronchus respiratory epithelial cells Medium Enhanced Q6PJT7 79882 +ENSG00000100722 ZC3H14 lung macrophages Medium Enhanced Q6PJT7 79882 +ENSG00000100722 ZC3H14 lung pneumocytes Medium Enhanced Q6PJT7 79882 +ENSG00000100749 VRK1 bronchus respiratory epithelial cells Medium Enhanced Q99986 7443 +ENSG00000100749 VRK1 lung macrophages Low Enhanced Q99986 7443 +ENSG00000100749 VRK1 lung pneumocytes Low Enhanced Q99986 7443 +ENSG00000100811 YY1 bronchus respiratory epithelial cells Medium Supported P25490 7528 +ENSG00000100811 YY1 lung macrophages Medium Supported P25490 7528 +ENSG00000100811 YY1 lung pneumocytes Medium Supported P25490 7528 +ENSG00000100813 ACIN1 bronchus respiratory epithelial cells Medium Supported Q9UKV3 22985 +ENSG00000100813 ACIN1 lung macrophages Low Supported Q9UKV3 22985 +ENSG00000100813 ACIN1 lung pneumocytes Medium Supported Q9UKV3 22985 +ENSG00000100815 TRIP11 bronchus respiratory epithelial cells High Supported Q15643 9321 +ENSG00000100815 TRIP11 lung macrophages High Supported Q15643 9321 +ENSG00000100815 TRIP11 lung pneumocytes High Supported Q15643 9321 +ENSG00000100823 APEX1 bronchus respiratory epithelial cells Medium Enhanced P27695 328 +ENSG00000100823 APEX1 lung macrophages Medium Enhanced P27695 328 +ENSG00000100823 APEX1 lung pneumocytes Medium Enhanced P27695 328 +ENSG00000100836 PABPN1 bronchus respiratory epithelial cells High Supported Q86U42 8106 +ENSG00000100836 PABPN1 lung macrophages Medium Supported Q86U42 8106 +ENSG00000100836 PABPN1 lung pneumocytes Medium Supported Q86U42 8106 +ENSG00000100889 PCK2 bronchus respiratory epithelial cells Low Enhanced Q16822 5106 +ENSG00000100889 PCK2 lung macrophages Medium Enhanced Q16822 5106 +ENSG00000100889 PCK2 lung pneumocytes Medium Enhanced Q16822 5106 +ENSG00000100926 TM9SF1 bronchus respiratory epithelial cells High Supported O15321 10548 +ENSG00000100926 TM9SF1 lung macrophages Low Supported O15321 10548 +ENSG00000100926 TM9SF1 lung pneumocytes Low Supported O15321 10548 +ENSG00000100941 PNN bronchus respiratory epithelial cells High Supported Q9H307 5411 +ENSG00000100941 PNN lung macrophages Medium Supported Q9H307 5411 +ENSG00000100941 PNN lung pneumocytes Medium Supported Q9H307 5411 +ENSG00000100982 PCIF1 bronchus respiratory epithelial cells Medium Enhanced Q9H4Z3 63935 +ENSG00000100982 PCIF1 lung macrophages Medium Enhanced Q9H4Z3 63935 +ENSG00000100982 PCIF1 lung pneumocytes Medium Enhanced Q9H4Z3 63935 +ENSG00000100983 GSS bronchus respiratory epithelial cells Medium Enhanced P48637 2937 +ENSG00000100983 GSS lung macrophages Low Enhanced P48637 2937 +ENSG00000101000 PROCR bronchus respiratory epithelial cells Medium Enhanced Q9UNN8 10544 +ENSG00000101017 CD40 lung macrophages Low Enhanced P25942 958 +ENSG00000101052 IFT52 bronchus respiratory epithelial cells High Enhanced Q9Y366 51098 +ENSG00000101052 IFT52 lung macrophages Low Enhanced Q9Y366 51098 +ENSG00000101052 IFT52 lung pneumocytes Low Enhanced Q9Y366 51098 +ENSG00000101096 NFATC2 bronchus respiratory epithelial cells Medium Enhanced Q13469 4773 +ENSG00000101096 NFATC2 lung pneumocytes Medium Enhanced Q13469 4773 +ENSG00000101126 ADNP bronchus respiratory epithelial cells High Supported Q9H2P0 23394 +ENSG00000101126 ADNP lung macrophages Medium Supported Q9H2P0 23394 +ENSG00000101126 ADNP lung pneumocytes High Supported Q9H2P0 23394 +ENSG00000101138 CSTF1 bronchus respiratory epithelial cells High Enhanced Q05048 1477 +ENSG00000101138 CSTF1 lung macrophages High Enhanced Q05048 1477 +ENSG00000101138 CSTF1 lung pneumocytes High Enhanced Q05048 1477 +ENSG00000101160 CTSZ bronchus respiratory epithelial cells High Supported Q9UBR2 1522 +ENSG00000101160 CTSZ lung macrophages High Supported Q9UBR2 1522 +ENSG00000101161 PRPF6 bronchus respiratory epithelial cells High Enhanced O94906 24148 +ENSG00000101161 PRPF6 lung macrophages High Enhanced O94906 24148 +ENSG00000101161 PRPF6 lung pneumocytes Low Enhanced O94906 24148 +ENSG00000101182 PSMA7 bronchus respiratory epithelial cells High Enhanced O14818 5688 +ENSG00000101182 PSMA7 lung macrophages High Enhanced O14818 5688 +ENSG00000101182 PSMA7 lung pneumocytes High Enhanced O14818 5688 +ENSG00000101191 DIDO1 bronchus respiratory epithelial cells High Supported Q9BTC0 11083 +ENSG00000101191 DIDO1 lung macrophages High Supported Q9BTC0 11083 +ENSG00000101191 DIDO1 lung pneumocytes High Supported Q9BTC0 11083 +ENSG00000101222 SPEF1 bronchus respiratory epithelial cells Medium Enhanced Q9Y4P9 25876 +ENSG00000101224 CDC25B lung pneumocytes Low Enhanced P30305 994 +ENSG00000101266 CSNK2A1 lung macrophages Medium Enhanced P68400 1457 +ENSG00000101266 CSNK2A1 lung pneumocytes Low Enhanced P68400 1457 +ENSG00000101333 PLCB4 bronchus respiratory epithelial cells Low Supported Q15147 5332 +ENSG00000101333 PLCB4 lung macrophages Low Supported Q15147 5332 +ENSG00000101347 SAMHD1 bronchus respiratory epithelial cells High Enhanced Q9Y3Z3 25939 +ENSG00000101347 SAMHD1 lung macrophages High Enhanced Q9Y3Z3 25939 +ENSG00000101347 SAMHD1 lung pneumocytes High Enhanced Q9Y3Z3 25939 +ENSG00000101361 NOP56 bronchus respiratory epithelial cells Medium Enhanced O00567 10528 +ENSG00000101361 NOP56 lung macrophages Low Enhanced O00567 10528 +ENSG00000101361 NOP56 lung pneumocytes Low Enhanced O00567 10528 +ENSG00000101365 IDH3B bronchus respiratory epithelial cells High Enhanced O43837 3420 +ENSG00000101365 IDH3B lung macrophages Medium Enhanced O43837 3420 +ENSG00000101365 IDH3B lung pneumocytes Medium Enhanced O43837 3420 +ENSG00000101367 MAPRE1 bronchus respiratory epithelial cells Medium Enhanced Q15691 22919 +ENSG00000101367 MAPRE1 lung macrophages Medium Enhanced Q15691 22919 +ENSG00000101384 JAG1 lung macrophages Low Enhanced P78504 182 +ENSG00000101384 JAG1 lung pneumocytes Low Enhanced P78504 182 +ENSG00000101412 E2F1 bronchus respiratory epithelial cells Medium Enhanced Q01094 1869 +ENSG00000101412 E2F1 lung macrophages Medium Enhanced Q01094 1869 +ENSG00000101412 E2F1 lung pneumocytes Low Enhanced Q01094 1869 +ENSG00000101413 RPRD1B bronchus respiratory epithelial cells Medium Supported Q9NQG5 58490 +ENSG00000101421 CHMP4B bronchus respiratory epithelial cells Low Enhanced Q9H444 128866 +ENSG00000101421 CHMP4B lung macrophages Low Enhanced Q9H444 128866 +ENSG00000101439 CST3 bronchus respiratory epithelial cells Medium Enhanced P01034 1471 +ENSG00000101439 CST3 lung macrophages Medium Enhanced P01034 1471 +ENSG00000101443 WFDC2 bronchus respiratory epithelial cells High Enhanced Q14508 10406 +ENSG00000101577 LPIN2 bronchus respiratory epithelial cells Medium Enhanced Q92539 9663 +ENSG00000101577 LPIN2 lung macrophages Low Enhanced Q92539 9663 +ENSG00000101577 LPIN2 lung pneumocytes Low Enhanced Q92539 9663 +ENSG00000101680 LAMA1 bronchus respiratory epithelial cells Low Enhanced P25391 284217 +ENSG00000101751 POLI bronchus respiratory epithelial cells Medium Enhanced Q9UNA4 11201 +ENSG00000101811 CSTF2 bronchus respiratory epithelial cells High Enhanced P33240 1478 +ENSG00000101811 CSTF2 lung macrophages Medium Enhanced P33240 1478 +ENSG00000101811 CSTF2 lung pneumocytes Medium Enhanced P33240 1478 +ENSG00000101846 STS bronchus respiratory epithelial cells Low Enhanced P08842 412 +ENSG00000101846 STS lung macrophages Low Enhanced P08842 412 +ENSG00000101856 PGRMC1 bronchus respiratory epithelial cells Medium Enhanced O00264 10857 +ENSG00000101856 PGRMC1 lung macrophages Low Enhanced O00264 10857 +ENSG00000101856 PGRMC1 lung pneumocytes Medium Enhanced O00264 10857 +ENSG00000101868 POLA1 bronchus respiratory epithelial cells Medium Enhanced P09884 5422 +ENSG00000101868 POLA1 lung macrophages Medium Enhanced P09884 5422 +ENSG00000101868 POLA1 lung pneumocytes Medium Enhanced P09884 5422 +ENSG00000101882 NKAP bronchus respiratory epithelial cells High Supported Q8N5F7 79576 +ENSG00000101882 NKAP lung macrophages High Supported Q8N5F7 79576 +ENSG00000101882 NKAP lung pneumocytes High Supported Q8N5F7 79576 +ENSG00000101916 TLR8 lung macrophages High Enhanced Q9NR97 51311 +ENSG00000101940 WDR13 bronchus respiratory epithelial cells Medium Enhanced Q9H1Z4 64743 +ENSG00000101940 WDR13 lung macrophages Medium Enhanced Q9H1Z4 64743 +ENSG00000101940 WDR13 lung pneumocytes Medium Enhanced Q9H1Z4 64743 +ENSG00000101972 STAG2 bronchus respiratory epithelial cells Medium Supported Q8N3U4 10735 +ENSG00000101972 STAG2 lung macrophages Medium Supported Q8N3U4 10735 +ENSG00000101972 STAG2 lung pneumocytes Medium Supported Q8N3U4 10735 +ENSG00000102024 PLS3 bronchus respiratory epithelial cells Medium Enhanced P13797 5358 +ENSG00000102024 PLS3 lung macrophages Medium Enhanced P13797 5358 +ENSG00000102024 PLS3 lung pneumocytes Medium Enhanced P13797 5358 +ENSG00000102030 NAA10 bronchus respiratory epithelial cells Medium Supported P41227 8260 +ENSG00000102030 NAA10 lung macrophages Low Supported P41227 8260 +ENSG00000102030 NAA10 lung pneumocytes Medium Supported P41227 8260 +ENSG00000102032 RENBP lung macrophages Medium Enhanced P51606 5973 +ENSG00000102034 ELF4 bronchus respiratory epithelial cells Medium Enhanced Q99607 2000 +ENSG00000102034 ELF4 lung macrophages Medium Enhanced Q99607 2000 +ENSG00000102034 ELF4 lung pneumocytes Low Enhanced Q99607 2000 +ENSG00000102054 RBBP7 bronchus respiratory epithelial cells High Supported Q16576 5931 +ENSG00000102054 RBBP7 lung macrophages High Supported Q16576 5931 +ENSG00000102054 RBBP7 lung pneumocytes High Supported Q16576 5931 +ENSG00000102098 SCML2 bronchus respiratory epithelial cells Low Enhanced Q9UQR0 10389 +ENSG00000102098 SCML2 lung pneumocytes Low Enhanced Q9UQR0 10389 +ENSG00000102103 PQBP1 bronchus respiratory epithelial cells High Supported O60828 10084 +ENSG00000102103 PQBP1 lung macrophages Low Supported O60828 10084 +ENSG00000102103 PQBP1 lung pneumocytes High Supported O60828 10084 +ENSG00000102119 EMD bronchus respiratory epithelial cells Medium Enhanced P50402 2010 +ENSG00000102119 EMD lung macrophages Medium Enhanced P50402 2010 +ENSG00000102119 EMD lung pneumocytes Medium Enhanced P50402 2010 +ENSG00000102181 CD99L2 bronchus respiratory epithelial cells Medium Enhanced Q8TCZ2 83692 +ENSG00000102181 CD99L2 lung macrophages Medium Enhanced Q8TCZ2 83692 +ENSG00000102181 CD99L2 lung pneumocytes Medium Enhanced Q8TCZ2 83692 +ENSG00000102189 EEA1 bronchus respiratory epithelial cells Low Enhanced Q15075 8411 +ENSG00000102189 EEA1 lung macrophages Medium Enhanced Q15075 8411 +ENSG00000102226 USP11 bronchus respiratory epithelial cells Low Enhanced P51784 8237 +ENSG00000102226 USP11 lung macrophages Low Enhanced P51784 8237 +ENSG00000102241 HTATSF1 bronchus respiratory epithelial cells High Supported O43719 27336 +ENSG00000102241 HTATSF1 lung macrophages High Supported O43719 27336 +ENSG00000102241 HTATSF1 lung pneumocytes High Supported O43719 27336 +ENSG00000102312 PORCN bronchus respiratory epithelial cells Low Enhanced Q9H237 64840 +ENSG00000102316 MAGED2 bronchus respiratory epithelial cells High Supported Q9UNF1 10916 +ENSG00000102316 MAGED2 lung macrophages Medium Supported Q9UNF1 10916 +ENSG00000102316 MAGED2 lung pneumocytes Medium Supported Q9UNF1 10916 +ENSG00000102317 RBM3 bronchus respiratory epithelial cells Medium Enhanced P98179 5935 +ENSG00000102317 RBM3 lung macrophages Medium Enhanced P98179 5935 +ENSG00000102317 RBM3 lung pneumocytes Low Enhanced P98179 5935 +ENSG00000102393 GLA bronchus respiratory epithelial cells Medium Enhanced P06280 2717 +ENSG00000102393 GLA lung macrophages Medium Enhanced P06280 2717 +ENSG00000102524 TNFSF13B bronchus respiratory epithelial cells Medium Enhanced Q9Y275 10673 +ENSG00000102524 TNFSF13B lung macrophages Medium Enhanced Q9Y275 10673 +ENSG00000102524 TNFSF13B lung pneumocytes Medium Enhanced Q9Y275 10673 +ENSG00000102572 STK24 bronchus respiratory epithelial cells Medium Enhanced Q9Y6E0 8428 +ENSG00000102572 STK24 lung macrophages Medium Enhanced Q9Y6E0 8428 +ENSG00000102572 STK24 lung pneumocytes Medium Enhanced Q9Y6E0 8428 +ENSG00000102575 ACP5 lung macrophages High Enhanced P13686 54 +ENSG00000102786 INTS6 bronchus respiratory epithelial cells Medium Supported Q9UL03 26512 +ENSG00000102786 INTS6 lung macrophages Medium Supported Q9UL03 26512 +ENSG00000102786 INTS6 lung pneumocytes Medium Supported Q9UL03 26512 +ENSG00000102854 MSLN bronchus respiratory epithelial cells Low Enhanced Q13421 10232 +ENSG00000102871 TRADD bronchus respiratory epithelial cells Medium Enhanced Q15628 8717 +ENSG00000102871 TRADD lung macrophages Medium Enhanced Q15628 8717 +ENSG00000102871 TRADD lung pneumocytes Medium Enhanced Q15628 8717 +ENSG00000102898 NUTF2 bronchus respiratory epithelial cells High Enhanced P61970 10204 +ENSG00000102898 NUTF2 lung pneumocytes Low Enhanced P61970 10204 +ENSG00000102934 PLLP bronchus respiratory epithelial cells Medium Enhanced Q9Y342 51090 +ENSG00000102934 PLLP lung pneumocytes Low Enhanced Q9Y342 51090 +ENSG00000102974 CTCF bronchus respiratory epithelial cells High Supported P49711 10664 +ENSG00000102974 CTCF lung macrophages Low Supported P49711 10664 +ENSG00000102974 CTCF lung pneumocytes High Supported P49711 10664 +ENSG00000102978 POLR2C bronchus respiratory epithelial cells Medium Enhanced P19387 5432 +ENSG00000102978 POLR2C lung macrophages Medium Enhanced P19387 5432 +ENSG00000102978 POLR2C lung pneumocytes Medium Enhanced P19387 5432 +ENSG00000102984 ZNF821 bronchus respiratory epithelial cells Low Enhanced O75541 55565 +ENSG00000102984 ZNF821 lung macrophages Low Enhanced O75541 55565 +ENSG00000103035 PSMD7 bronchus respiratory epithelial cells Medium Enhanced P51665 5713 +ENSG00000103035 PSMD7 lung macrophages Medium Enhanced P51665 5713 +ENSG00000103035 PSMD7 lung pneumocytes High Enhanced P51665 5713 +ENSG00000103066 PLA2G15 bronchus respiratory epithelial cells High Enhanced Q8NCC3 23659 +ENSG00000103066 PLA2G15 lung macrophages High Enhanced Q8NCC3 23659 +ENSG00000103066 PLA2G15 lung pneumocytes Medium Enhanced Q8NCC3 23659 +ENSG00000103150 MLYCD bronchus respiratory epithelial cells Medium Enhanced O95822 23417 +ENSG00000103150 MLYCD lung macrophages Medium Enhanced O95822 23417 +ENSG00000103187 COTL1 lung macrophages Medium Enhanced Q14019 23406 +ENSG00000103194 USP10 bronchus respiratory epithelial cells High Enhanced Q14694 9100 +ENSG00000103194 USP10 lung macrophages High Enhanced Q14694 9100 +ENSG00000103194 USP10 lung pneumocytes High Enhanced Q14694 9100 +ENSG00000103199 ZNF500 bronchus respiratory epithelial cells Medium Supported O60304 26048 +ENSG00000103199 ZNF500 lung macrophages Low Supported O60304 26048 +ENSG00000103199 ZNF500 lung pneumocytes Low Supported O60304 26048 +ENSG00000103249 CLCN7 bronchus respiratory epithelial cells Medium Supported P51798 1186 +ENSG00000103249 CLCN7 lung macrophages Medium Supported P51798 1186 +ENSG00000103249 CLCN7 lung pneumocytes Low Supported P51798 1186 +ENSG00000103254 FAM173A bronchus respiratory epithelial cells Low Enhanced Q9BQD7 65990 +ENSG00000103254 FAM173A lung macrophages Medium Enhanced Q9BQD7 65990 +ENSG00000103254 FAM173A lung pneumocytes Medium Enhanced Q9BQD7 65990 +ENSG00000103266 STUB1 bronchus respiratory epithelial cells High Enhanced Q9UNE7 10273 +ENSG00000103266 STUB1 lung macrophages Low Enhanced Q9UNE7 10273 +ENSG00000103266 STUB1 lung pneumocytes Low Enhanced Q9UNE7 10273 +ENSG00000103274 NUBP1 bronchus respiratory epithelial cells Medium Enhanced P53384 4682 +ENSG00000103274 NUBP1 lung macrophages Medium Enhanced P53384 4682 +ENSG00000103274 NUBP1 lung pneumocytes Low Enhanced P53384 4682 +ENSG00000103316 CRYM bronchus respiratory epithelial cells Low Enhanced I3NI53 NA +ENSG00000103316 CRYM lung pneumocytes Medium Enhanced I3NI53 NA +ENSG00000103415 HMOX2 bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000103415 HMOX2 lung macrophages High Supported NA NA +ENSG00000103415 HMOX2 lung pneumocytes Medium Supported NA NA +ENSG00000103460 TOX3 bronchus respiratory epithelial cells Medium Enhanced O15405 27324 +ENSG00000103479 RBL2 bronchus respiratory epithelial cells Medium Supported Q08999 5934 +ENSG00000103479 RBL2 lung macrophages High Supported Q08999 5934 +ENSG00000103479 RBL2 lung pneumocytes Medium Supported Q08999 5934 +ENSG00000103490 PYCARD bronchus respiratory epithelial cells Medium Enhanced Q9ULZ3 29108 +ENSG00000103490 PYCARD lung macrophages High Enhanced Q9ULZ3 29108 +ENSG00000103507 BCKDK bronchus respiratory epithelial cells High Supported O14874 10295 +ENSG00000103507 BCKDK lung macrophages Medium Supported O14874 10295 +ENSG00000103534 TMC5 bronchus respiratory epithelial cells Medium Enhanced Q6UXY8 79838 +ENSG00000103534 TMC5 lung macrophages Medium Enhanced Q6UXY8 79838 +ENSG00000103591 AAGAB bronchus respiratory epithelial cells High Supported Q6PD74 79719 +ENSG00000103591 AAGAB lung macrophages Medium Supported Q6PD74 79719 +ENSG00000103591 AAGAB lung pneumocytes Medium Supported Q6PD74 79719 +ENSG00000103642 LACTB bronchus respiratory epithelial cells Medium Enhanced P83111 114294 +ENSG00000103642 LACTB lung macrophages Medium Enhanced P83111 114294 +ENSG00000103642 LACTB lung pneumocytes Low Enhanced P83111 114294 +ENSG00000103647 CORO2B bronchus respiratory epithelial cells Low Enhanced Q9UQ03 10391 +ENSG00000103647 CORO2B lung macrophages Low Enhanced Q9UQ03 10391 +ENSG00000103647 CORO2B lung pneumocytes Low Enhanced Q9UQ03 10391 +ENSG00000103811 CTSH bronchus respiratory epithelial cells Medium Enhanced P09668 1512 +ENSG00000103811 CTSH lung macrophages High Enhanced P09668 1512 +ENSG00000103811 CTSH lung pneumocytes Low Enhanced P09668 1512 +ENSG00000103855 CD276 bronchus respiratory epithelial cells Medium Enhanced Q5ZPR3 80381 +ENSG00000103855 CD276 lung macrophages Medium Enhanced Q5ZPR3 80381 +ENSG00000103855 CD276 lung pneumocytes Low Enhanced Q5ZPR3 80381 +ENSG00000103978 TMEM87A bronchus respiratory epithelial cells Medium Enhanced Q8NBN3 25963 +ENSG00000103978 TMEM87A lung macrophages Low Enhanced Q8NBN3 25963 +ENSG00000103978 TMEM87A lung pneumocytes Medium Enhanced Q8NBN3 25963 +ENSG00000104064 GABPB1 bronchus respiratory epithelial cells High Supported Q06547 2553 +ENSG00000104064 GABPB1 lung macrophages High Supported Q06547 2553 +ENSG00000104064 GABPB1 lung pneumocytes High Supported Q06547 2553 +ENSG00000104067 TJP1 bronchus respiratory epithelial cells Medium Enhanced G3V1L9 7082 +ENSG00000104067 TJP1 lung pneumocytes Low Enhanced G3V1L9 7082 +ENSG00000104140 RHOV bronchus respiratory epithelial cells Low Enhanced Q96L33 171177 +ENSG00000104177 MYEF2 bronchus respiratory epithelial cells High Supported Q9P2K5 50804 +ENSG00000104177 MYEF2 lung macrophages High Supported Q9P2K5 50804 +ENSG00000104177 MYEF2 lung pneumocytes Medium Supported Q9P2K5 50804 +ENSG00000104205 SGK3 bronchus respiratory epithelial cells Medium Supported Q96BR1 100533105; 23678 +ENSG00000104205 SGK3 lung macrophages Medium Supported Q96BR1 100533105; 23678 +ENSG00000104205 SGK3 lung pneumocytes Low Supported Q96BR1 100533105; 23678 +ENSG00000104221 BRF2 bronchus respiratory epithelial cells High Enhanced Q9HAW0 55290 +ENSG00000104221 BRF2 lung macrophages Medium Enhanced Q9HAW0 55290 +ENSG00000104221 BRF2 lung pneumocytes Medium Enhanced Q9HAW0 55290 +ENSG00000104267 CA2 lung macrophages Medium Enhanced P00918 760 +ENSG00000104267 CA2 lung pneumocytes Low Enhanced P00918 760 +ENSG00000104320 NBN bronchus respiratory epithelial cells Medium Supported O60934 4683 +ENSG00000104320 NBN lung macrophages Medium Supported O60934 4683 +ENSG00000104320 NBN lung pneumocytes Medium Supported O60934 4683 +ENSG00000104325 DECR1 bronchus respiratory epithelial cells Medium Enhanced Q16698 1666 +ENSG00000104325 DECR1 lung macrophages High Enhanced Q16698 1666 +ENSG00000104325 DECR1 lung pneumocytes Low Enhanced Q16698 1666 +ENSG00000104331 IMPAD1 bronchus respiratory epithelial cells Medium Supported Q9NX62 54928 +ENSG00000104331 IMPAD1 lung macrophages Medium Supported Q9NX62 54928 +ENSG00000104331 IMPAD1 lung pneumocytes Low Supported Q9NX62 54928 +ENSG00000104365 IKBKB bronchus respiratory epithelial cells Low Enhanced O14920 3551 +ENSG00000104365 IKBKB lung macrophages Medium Enhanced O14920 3551 +ENSG00000104365 IKBKB lung pneumocytes Medium Enhanced O14920 3551 +ENSG00000104368 PLAT bronchus respiratory epithelial cells Low Supported P00750 5327 +ENSG00000104381 GDAP1 bronchus respiratory epithelial cells Low Enhanced Q8TB36 54332 +ENSG00000104413 ESRP1 bronchus respiratory epithelial cells Medium Enhanced Q6NXG1 54845 +ENSG00000104413 ESRP1 lung macrophages Low Enhanced Q6NXG1 54845 +ENSG00000104413 ESRP1 lung pneumocytes Low Enhanced Q6NXG1 54845 +ENSG00000104447 TRPS1 bronchus respiratory epithelial cells Medium Enhanced Q9UHF7 7227 +ENSG00000104450 SPAG1 bronchus respiratory epithelial cells Medium Enhanced Q07617 6674 +ENSG00000104529 EEF1D bronchus respiratory epithelial cells High Supported E9PMW7 NA +ENSG00000104529 EEF1D lung macrophages Medium Supported E9PMW7 NA +ENSG00000104529 EEF1D lung pneumocytes Medium Supported E9PMW7 NA +ENSG00000104549 SQLE bronchus respiratory epithelial cells Low Enhanced Q14534 6713 +ENSG00000104549 SQLE lung macrophages Medium Enhanced Q14534 6713 +ENSG00000104611 SH2D4A bronchus respiratory epithelial cells Medium Enhanced Q9H788 63898 +ENSG00000104611 SH2D4A lung macrophages Low Enhanced Q9H788 63898 +ENSG00000104611 SH2D4A lung pneumocytes Low Enhanced Q9H788 63898 +ENSG00000104738 MCM4 bronchus respiratory epithelial cells High Supported P33991 4173 +ENSG00000104738 MCM4 lung macrophages Medium Supported P33991 4173 +ENSG00000104738 MCM4 lung pneumocytes High Supported P33991 4173 +ENSG00000104763 ASAH1 bronchus respiratory epithelial cells Medium Supported Q13510 427 +ENSG00000104763 ASAH1 lung macrophages High Supported Q13510 427 +ENSG00000104763 ASAH1 lung pneumocytes Low Supported Q13510 427 +ENSG00000104765 BNIP3L bronchus respiratory epithelial cells Medium Enhanced O60238 665 +ENSG00000104765 BNIP3L lung macrophages Medium Enhanced O60238 665 +ENSG00000104765 BNIP3L lung pneumocytes Medium Enhanced O60238 665 +ENSG00000104774 MAN2B1 bronchus respiratory epithelial cells High Supported O00754 4125 +ENSG00000104774 MAN2B1 lung macrophages High Supported O00754 4125 +ENSG00000104805 NUCB1 lung macrophages Medium Enhanced Q02818 4924 +ENSG00000104805 NUCB1 lung pneumocytes Medium Enhanced Q02818 4924 +ENSG00000104812 GYS1 bronchus respiratory epithelial cells High Enhanced P13807 2997 +ENSG00000104812 GYS1 lung macrophages High Enhanced P13807 2997 +ENSG00000104812 GYS1 lung pneumocytes Low Enhanced P13807 2997 +ENSG00000104823 ECH1 bronchus respiratory epithelial cells Medium Supported M0QZX8 NA +ENSG00000104823 ECH1 lung macrophages High Supported M0QZX8 NA +ENSG00000104823 ECH1 lung pneumocytes Medium Supported M0QZX8 NA +ENSG00000104824 HNRNPL bronchus respiratory epithelial cells High Supported B4DVF8 NA +ENSG00000104824 HNRNPL lung macrophages High Supported B4DVF8 NA +ENSG00000104824 HNRNPL lung pneumocytes High Supported B4DVF8 NA +ENSG00000104852 SNRNP70 bronchus respiratory epithelial cells High Supported P08621 6625 +ENSG00000104852 SNRNP70 lung macrophages Medium Supported P08621 6625 +ENSG00000104852 SNRNP70 lung pneumocytes High Supported P08621 6625 +ENSG00000104897 SF3A2 bronchus respiratory epithelial cells Medium Enhanced Q15428 8175 +ENSG00000104897 SF3A2 lung macrophages Medium Enhanced Q15428 8175 +ENSG00000104897 SF3A2 lung pneumocytes Medium Enhanced Q15428 8175 +ENSG00000104938 CLEC4M lung macrophages Low Supported Q9H2X3 10332 +ENSG00000104976 SNAPC2 bronchus respiratory epithelial cells High Supported Q13487 6618 +ENSG00000104976 SNAPC2 lung macrophages Medium Supported Q13487 6618 +ENSG00000104976 SNAPC2 lung pneumocytes Medium Supported Q13487 6618 +ENSG00000104980 TIMM44 bronchus respiratory epithelial cells High Supported O43615 10469 +ENSG00000104980 TIMM44 lung macrophages Medium Supported O43615 10469 +ENSG00000104980 TIMM44 lung pneumocytes Low Supported O43615 10469 +ENSG00000105127 AKAP8 bronchus respiratory epithelial cells High Supported O43823 10270 +ENSG00000105127 AKAP8 lung macrophages Low Supported O43823 10270 +ENSG00000105127 AKAP8 lung pneumocytes High Supported O43823 10270 +ENSG00000105143 SLC1A6 lung macrophages Low Enhanced P48664 6511 +ENSG00000105185 PDCD5 bronchus respiratory epithelial cells Medium Enhanced O14737 9141 +ENSG00000105185 PDCD5 lung macrophages Medium Enhanced O14737 9141 +ENSG00000105197 TIMM50 bronchus respiratory epithelial cells Medium Enhanced Q3ZCQ8 92609 +ENSG00000105197 TIMM50 lung macrophages Low Enhanced Q3ZCQ8 92609 +ENSG00000105197 TIMM50 lung pneumocytes Low Enhanced Q3ZCQ8 92609 +ENSG00000105202 FBL bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000105202 FBL lung pneumocytes Medium Supported NA NA +ENSG00000105220 GPI bronchus respiratory epithelial cells Medium Enhanced P06744 2821 +ENSG00000105220 GPI lung macrophages Medium Enhanced P06744 2821 +ENSG00000105220 GPI lung pneumocytes Low Enhanced P06744 2821 +ENSG00000105281 SLC1A5 bronchus respiratory epithelial cells Medium Enhanced Q15758 6510 +ENSG00000105281 SLC1A5 lung macrophages Medium Enhanced Q15758 6510 +ENSG00000105281 SLC1A5 lung pneumocytes Low Enhanced Q15758 6510 +ENSG00000105287 PRKD2 bronchus respiratory epithelial cells Medium Enhanced Q9BZL6 25865 +ENSG00000105287 PRKD2 lung macrophages Low Enhanced Q9BZL6 25865 +ENSG00000105289 TJP3 bronchus respiratory epithelial cells Medium Enhanced O95049 27134 +ENSG00000105289 TJP3 lung pneumocytes Low Enhanced O95049 27134 +ENSG00000105323 HNRNPUL1 bronchus respiratory epithelial cells High Enhanced Q9BUJ2 11100 +ENSG00000105323 HNRNPUL1 lung macrophages High Enhanced Q9BUJ2 11100 +ENSG00000105323 HNRNPUL1 lung pneumocytes High Enhanced Q9BUJ2 11100 +ENSG00000105357 MYH14 bronchus respiratory epithelial cells High Enhanced Q7Z406 79784 +ENSG00000105357 MYH14 lung pneumocytes High Enhanced Q7Z406 79784 +ENSG00000105369 CD79A lung macrophages Low Enhanced P11912 973 +ENSG00000105379 ETFB bronchus respiratory epithelial cells Medium Supported P38117 2109 +ENSG00000105379 ETFB lung macrophages High Supported P38117 2109 +ENSG00000105379 ETFB lung pneumocytes Low Supported P38117 2109 +ENSG00000105388 CEACAM5 lung pneumocytes Low Enhanced P06731 1048 +ENSG00000105401 CDC37 bronchus respiratory epithelial cells Medium Supported Q16543 11140 +ENSG00000105401 CDC37 lung macrophages Medium Supported Q16543 11140 +ENSG00000105401 CDC37 lung pneumocytes Medium Supported Q16543 11140 +ENSG00000105404 RABAC1 bronchus respiratory epithelial cells High Enhanced Q9UI14 10567 +ENSG00000105404 RABAC1 lung pneumocytes Low Enhanced Q9UI14 10567 +ENSG00000105483 CARD8 bronchus respiratory epithelial cells Medium Supported Q9Y2G2 22900 +ENSG00000105483 CARD8 lung macrophages Medium Supported Q9Y2G2 22900 +ENSG00000105483 CARD8 lung pneumocytes Medium Supported Q9Y2G2 22900 +ENSG00000105519 CAPS bronchus respiratory epithelial cells High Enhanced Q13938 NA +ENSG00000105519 CAPS lung pneumocytes Low Enhanced Q13938 NA +ENSG00000105552 BCAT2 bronchus respiratory epithelial cells High Enhanced O15382 587 +ENSG00000105552 BCAT2 lung pneumocytes Medium Enhanced O15382 587 +ENSG00000105607 GCDH bronchus respiratory epithelial cells High Enhanced Q92947 2639 +ENSG00000105607 GCDH lung macrophages Low Enhanced Q92947 2639 +ENSG00000105607 GCDH lung pneumocytes Medium Enhanced Q92947 2639 +ENSG00000105612 DNASE2 bronchus respiratory epithelial cells Low Enhanced O00115 1777 +ENSG00000105618 PRPF31 bronchus respiratory epithelial cells High Supported NA NA +ENSG00000105618 PRPF31 lung macrophages Medium Supported NA NA +ENSG00000105618 PRPF31 lung pneumocytes High Supported NA NA +ENSG00000105639 JAK3 lung macrophages Low Enhanced P52333 3718 +ENSG00000105650 PDE4C bronchus respiratory epithelial cells Low Enhanced Q08493 5143 +ENSG00000105650 PDE4C lung macrophages Low Enhanced Q08493 5143 +ENSG00000105655 ISYNA1 bronchus respiratory epithelial cells Low Enhanced Q9NPH2 51477 +ENSG00000105669 COPE bronchus respiratory epithelial cells Medium Supported O14579 11316 +ENSG00000105669 COPE lung macrophages Medium Supported O14579 11316 +ENSG00000105669 COPE lung pneumocytes Medium Supported O14579 11316 +ENSG00000105671 DDX49 bronchus respiratory epithelial cells High Enhanced Q9Y6V7 54555 +ENSG00000105671 DDX49 lung macrophages High Enhanced Q9Y6V7 54555 +ENSG00000105671 DDX49 lung pneumocytes Medium Enhanced Q9Y6V7 54555 +ENSG00000105676 ARMC6 bronchus respiratory epithelial cells Medium Supported Q6NXE6 93436 +ENSG00000105676 ARMC6 lung macrophages Medium Supported Q6NXE6 93436 +ENSG00000105676 ARMC6 lung pneumocytes Medium Supported Q6NXE6 93436 +ENSG00000105701 FKBP8 bronchus respiratory epithelial cells Medium Supported Q14318 23770 +ENSG00000105701 FKBP8 lung macrophages Medium Supported Q14318 23770 +ENSG00000105701 FKBP8 lung pneumocytes Low Supported Q14318 23770 +ENSG00000105755 ETHE1 bronchus respiratory epithelial cells Low Enhanced O95571 23474 +ENSG00000105755 ETHE1 lung macrophages Medium Enhanced O95571 23474 +ENSG00000105755 ETHE1 lung pneumocytes Low Enhanced O95571 23474 +ENSG00000105767 CADM4 bronchus respiratory epithelial cells Low Enhanced Q8NFZ8 199731 +ENSG00000105767 CADM4 lung macrophages Low Enhanced Q8NFZ8 199731 +ENSG00000105810 CDK6 bronchus respiratory epithelial cells Low Enhanced Q00534 1021 +ENSG00000105810 CDK6 lung macrophages Medium Enhanced Q00534 1021 +ENSG00000105854 PON2 bronchus respiratory epithelial cells Medium Enhanced Q15165 5445 +ENSG00000105854 PON2 lung macrophages Medium Enhanced Q15165 5445 +ENSG00000105854 PON2 lung pneumocytes High Enhanced Q15165 5445 +ENSG00000105855 ITGB8 bronchus respiratory epithelial cells Medium Supported P26012 3696 +ENSG00000105855 ITGB8 lung pneumocytes Low Supported P26012 3696 +ENSG00000105879 CBLL1 bronchus respiratory epithelial cells Medium Enhanced Q75N03 79872 +ENSG00000105879 CBLL1 lung macrophages Low Enhanced Q75N03 79872 +ENSG00000105879 CBLL1 lung pneumocytes Medium Enhanced Q75N03 79872 +ENSG00000105926 MPP6 bronchus respiratory epithelial cells Low Enhanced Q9NZW5 51678 +ENSG00000105926 MPP6 lung macrophages Low Enhanced Q9NZW5 51678 +ENSG00000105948 TTC26 bronchus respiratory epithelial cells Medium Enhanced A0AVF1 79989 +ENSG00000105953 OGDH bronchus respiratory epithelial cells High Supported Q02218 4967 +ENSG00000105953 OGDH lung macrophages High Supported Q02218 4967 +ENSG00000105953 OGDH lung pneumocytes Medium Supported Q02218 4967 +ENSG00000105963 ADAP1 bronchus respiratory epithelial cells Low Enhanced O75689 11033 +ENSG00000105963 ADAP1 lung macrophages Low Enhanced O75689 11033 +ENSG00000105968 H2AFV bronchus respiratory epithelial cells Medium Supported Q71UI9 94239 +ENSG00000105968 H2AFV lung macrophages Medium Supported Q71UI9 94239 +ENSG00000105968 H2AFV lung pneumocytes Medium Supported Q71UI9 94239 +ENSG00000105971 CAV2 bronchus respiratory epithelial cells High Enhanced P51636 858 +ENSG00000105971 CAV2 lung pneumocytes High Enhanced P51636 858 +ENSG00000105974 CAV1 bronchus respiratory epithelial cells Medium Enhanced Q03135 857 +ENSG00000105974 CAV1 lung macrophages Medium Enhanced Q03135 857 +ENSG00000105974 CAV1 lung pneumocytes High Enhanced Q03135 857 +ENSG00000105993 DNAJB6 bronchus respiratory epithelial cells Medium Enhanced O75190 10049 +ENSG00000105993 DNAJB6 lung pneumocytes Medium Enhanced O75190 10049 +ENSG00000106028 SSBP1 bronchus respiratory epithelial cells Low Enhanced E7EUY5 NA +ENSG00000106028 SSBP1 lung macrophages Medium Enhanced E7EUY5 NA +ENSG00000106049 HIBADH bronchus respiratory epithelial cells High Enhanced P31937 11112 +ENSG00000106049 HIBADH lung macrophages High Enhanced P31937 11112 +ENSG00000106049 HIBADH lung pneumocytes Low Enhanced P31937 11112 +ENSG00000106066 CPVL lung macrophages Medium Enhanced Q9H3G5 54504 +ENSG00000106078 COBL bronchus respiratory epithelial cells Medium Enhanced O75128 23242 +ENSG00000106078 COBL lung macrophages Medium Enhanced O75128 23242 +ENSG00000106078 COBL lung pneumocytes Low Enhanced O75128 23242 +ENSG00000106105 GARS bronchus respiratory epithelial cells Medium Enhanced P41250 2617 +ENSG00000106105 GARS lung macrophages Medium Enhanced P41250 2617 +ENSG00000106105 GARS lung pneumocytes Low Enhanced P41250 2617 +ENSG00000106211 HSPB1 bronchus respiratory epithelial cells High Enhanced P04792 3315 +ENSG00000106211 HSPB1 lung macrophages Medium Enhanced P04792 3315 +ENSG00000106211 HSPB1 lung pneumocytes Low Enhanced P04792 3315 +ENSG00000106299 WASL bronchus respiratory epithelial cells Medium Supported O00401 8976 +ENSG00000106299 WASL lung macrophages Medium Supported O00401 8976 +ENSG00000106299 WASL lung pneumocytes High Supported O00401 8976 +ENSG00000106305 AIMP2 bronchus respiratory epithelial cells Medium Supported Q13155 7965 +ENSG00000106305 AIMP2 lung macrophages Medium Supported Q13155 7965 +ENSG00000106305 AIMP2 lung pneumocytes Low Supported Q13155 7965 +ENSG00000106344 RBM28 bronchus respiratory epithelial cells Medium Enhanced Q9NW13 55131 +ENSG00000106344 RBM28 lung macrophages Low Enhanced Q9NW13 55131 +ENSG00000106344 RBM28 lung pneumocytes Low Enhanced Q9NW13 55131 +ENSG00000106367 AP1S1 bronchus respiratory epithelial cells Medium Supported P61966 1174 +ENSG00000106367 AP1S1 lung macrophages Low Supported P61966 1174 +ENSG00000106392 C1GALT1 bronchus respiratory epithelial cells Medium Enhanced Q9NS00 56913 +ENSG00000106392 C1GALT1 lung macrophages Medium Enhanced Q9NS00 56913 +ENSG00000106392 C1GALT1 lung pneumocytes Medium Enhanced Q9NS00 56913 +ENSG00000106443 PHF14 bronchus respiratory epithelial cells High Supported O94880 9678 +ENSG00000106443 PHF14 lung macrophages High Supported O94880 9678 +ENSG00000106443 PHF14 lung pneumocytes High Supported O94880 9678 +ENSG00000106462 EZH2 bronchus respiratory epithelial cells Medium Enhanced Q15910 2146 +ENSG00000106462 EZH2 lung macrophages Low Enhanced Q15910 2146 +ENSG00000106541 AGR2 bronchus respiratory epithelial cells High Enhanced O95994 10551 +ENSG00000106541 AGR2 lung pneumocytes Medium Enhanced O95994 10551 +ENSG00000106546 AHR bronchus respiratory epithelial cells Medium Enhanced P35869 196 +ENSG00000106546 AHR lung macrophages Low Enhanced P35869 196 +ENSG00000106554 CHCHD3 bronchus respiratory epithelial cells High Enhanced Q9NX63 54927 +ENSG00000106554 CHCHD3 lung macrophages High Enhanced Q9NX63 54927 +ENSG00000106554 CHCHD3 lung pneumocytes High Enhanced Q9NX63 54927 +ENSG00000106624 AEBP1 bronchus respiratory epithelial cells Low Enhanced Q8IUX7 165 +ENSG00000106624 AEBP1 lung macrophages Low Enhanced Q8IUX7 165 +ENSG00000106624 AEBP1 lung pneumocytes Low Enhanced Q8IUX7 165 +ENSG00000106665 CLIP2 bronchus respiratory epithelial cells Medium Enhanced Q9UDT6 7461 +ENSG00000106665 CLIP2 lung macrophages Medium Enhanced Q9UDT6 7461 +ENSG00000106665 CLIP2 lung pneumocytes Medium Enhanced Q9UDT6 7461 +ENSG00000106686 SPATA6L bronchus respiratory epithelial cells Low Enhanced Q8N4H0 55064 +ENSG00000106789 CORO2A bronchus respiratory epithelial cells Medium Enhanced Q92828 7464 +ENSG00000106789 CORO2A lung macrophages Medium Enhanced Q92828 7464 +ENSG00000106853 PTGR1 bronchus respiratory epithelial cells Low Enhanced Q14914 22949 +ENSG00000106992 AK1 bronchus respiratory epithelial cells Low Enhanced P00568 203 +ENSG00000106992 AK1 lung pneumocytes Medium Enhanced P00568 203 +ENSG00000107020 PLGRKT bronchus respiratory epithelial cells High Enhanced Q9HBL7 55848 +ENSG00000107020 PLGRKT lung macrophages High Enhanced Q9HBL7 55848 +ENSG00000107020 PLGRKT lung pneumocytes Low Enhanced Q9HBL7 55848 +ENSG00000107036 RIC1 bronchus respiratory epithelial cells Medium Supported Q4ADV7 57589 +ENSG00000107036 RIC1 lung macrophages Medium Supported Q4ADV7 57589 +ENSG00000107036 RIC1 lung pneumocytes Low Supported Q4ADV7 57589 +ENSG00000107099 DOCK8 bronchus respiratory epithelial cells Low Enhanced Q8NF50 81704 +ENSG00000107099 DOCK8 lung macrophages High Enhanced Q8NF50 81704 +ENSG00000107262 BAG1 bronchus respiratory epithelial cells Medium Enhanced Q99933 573 +ENSG00000107262 BAG1 lung macrophages Low Enhanced Q99933 573 +ENSG00000107262 BAG1 lung pneumocytes Medium Enhanced Q99933 573 +ENSG00000107371 EXOSC3 bronchus respiratory epithelial cells High Enhanced Q9NQT5 51010 +ENSG00000107371 EXOSC3 lung macrophages Medium Enhanced Q9NQT5 51010 +ENSG00000107371 EXOSC3 lung pneumocytes Medium Enhanced Q9NQT5 51010 +ENSG00000107537 PHYH bronchus respiratory epithelial cells Medium Enhanced O14832 5264 +ENSG00000107537 PHYH lung macrophages Medium Enhanced O14832 5264 +ENSG00000107581 EIF3A bronchus respiratory epithelial cells Medium Enhanced Q14152 8661 +ENSG00000107581 EIF3A lung macrophages Medium Enhanced Q14152 8661 +ENSG00000107581 EIF3A lung pneumocytes Medium Enhanced Q14152 8661 +ENSG00000107742 SPOCK2 bronchus respiratory epithelial cells Medium Supported Q92563 9806 +ENSG00000107742 SPOCK2 lung macrophages Medium Supported Q92563 9806 +ENSG00000107742 SPOCK2 lung pneumocytes Low Supported Q92563 9806 +ENSG00000107798 LIPA bronchus respiratory epithelial cells Low Enhanced P38571 3988 +ENSG00000107798 LIPA lung macrophages High Enhanced P38571 3988 +ENSG00000107882 SUFU bronchus respiratory epithelial cells Medium Enhanced Q9UMX1 51684 +ENSG00000107882 SUFU lung macrophages Low Enhanced Q9UMX1 51684 +ENSG00000107882 SUFU lung pneumocytes Low Enhanced Q9UMX1 51684 +ENSG00000107897 ACBD5 bronchus respiratory epithelial cells High Enhanced Q5T8D3 91452 +ENSG00000107897 ACBD5 lung macrophages High Enhanced Q5T8D3 91452 +ENSG00000107897 ACBD5 lung pneumocytes Medium Enhanced Q5T8D3 91452 +ENSG00000107902 LHPP bronchus respiratory epithelial cells Medium Enhanced Q9H008 64077 +ENSG00000107902 LHPP lung macrophages Medium Enhanced Q9H008 64077 +ENSG00000107959 PITRM1 bronchus respiratory epithelial cells Medium Enhanced Q5JRX3 10531 +ENSG00000107959 PITRM1 lung macrophages High Enhanced Q5JRX3 10531 +ENSG00000107959 PITRM1 lung pneumocytes Medium Enhanced Q5JRX3 10531 +ENSG00000107968 MAP3K8 bronchus respiratory epithelial cells High Supported P41279 1326 +ENSG00000107968 MAP3K8 lung macrophages Medium Supported P41279 1326 +ENSG00000107968 MAP3K8 lung pneumocytes Low Supported P41279 1326 +ENSG00000108039 XPNPEP1 bronchus respiratory epithelial cells Low Supported Q9NQW7 7511 +ENSG00000108039 XPNPEP1 lung macrophages Low Supported Q9NQW7 7511 +ENSG00000108064 TFAM bronchus respiratory epithelial cells Medium Supported Q00059 7019 +ENSG00000108064 TFAM lung macrophages Low Supported Q00059 7019 +ENSG00000108091 CCDC6 bronchus respiratory epithelial cells Medium Enhanced Q16204 8030 +ENSG00000108091 CCDC6 lung macrophages Low Enhanced Q16204 8030 +ENSG00000108176 DNAJC12 bronchus respiratory epithelial cells Medium Enhanced Q9UKB3 56521 +ENSG00000108176 DNAJC12 lung pneumocytes Low Enhanced Q9UKB3 56521 +ENSG00000108312 UBTF bronchus respiratory epithelial cells High Enhanced P17480 7343 +ENSG00000108312 UBTF lung macrophages High Enhanced P17480 7343 +ENSG00000108312 UBTF lung pneumocytes High Enhanced P17480 7343 +ENSG00000108381 ASPA bronchus respiratory epithelial cells Low Enhanced P45381 443 +ENSG00000108424 KPNB1 bronchus respiratory epithelial cells Medium Enhanced Q14974 3837 +ENSG00000108424 KPNB1 lung macrophages Medium Enhanced Q14974 3837 +ENSG00000108439 PNPO bronchus respiratory epithelial cells Medium Enhanced Q9NVS9 55163 +ENSG00000108439 PNPO lung macrophages Low Enhanced Q9NVS9 55163 +ENSG00000108439 PNPO lung pneumocytes Medium Enhanced Q9NVS9 55163 +ENSG00000108465 CDK5RAP3 bronchus respiratory epithelial cells High Supported Q96JB5 80279 +ENSG00000108465 CDK5RAP3 lung macrophages Medium Supported Q96JB5 80279 +ENSG00000108465 CDK5RAP3 lung pneumocytes Medium Supported Q96JB5 80279 +ENSG00000108468 CBX1 bronchus respiratory epithelial cells High Supported P83916 10951 +ENSG00000108468 CBX1 lung macrophages Medium Supported P83916 10951 +ENSG00000108468 CBX1 lung pneumocytes Medium Supported P83916 10951 +ENSG00000108518 PFN1 bronchus respiratory epithelial cells Medium Enhanced P07737 5216 +ENSG00000108518 PFN1 lung macrophages High Enhanced P07737 5216 +ENSG00000108518 PFN1 lung pneumocytes Low Enhanced P07737 5216 +ENSG00000108561 C1QBP bronchus respiratory epithelial cells Medium Supported Q07021 708 +ENSG00000108561 C1QBP lung macrophages Medium Supported Q07021 708 +ENSG00000108561 C1QBP lung pneumocytes Medium Supported Q07021 708 +ENSG00000108592 FTSJ3 bronchus respiratory epithelial cells Low Supported Q8IY81 117246 +ENSG00000108602 ALDH3A1 bronchus respiratory epithelial cells Medium Enhanced P30838 218 +ENSG00000108651 UTP6 bronchus respiratory epithelial cells Low Enhanced Q9NYH9 55813 +ENSG00000108651 UTP6 lung macrophages Medium Enhanced Q9NYH9 55813 +ENSG00000108654 DDX5 bronchus respiratory epithelial cells High Supported P17844 1655 +ENSG00000108654 DDX5 lung pneumocytes Medium Supported P17844 1655 +ENSG00000108679 LGALS3BP bronchus respiratory epithelial cells Low Supported Q08380 3959 +ENSG00000108679 LGALS3BP lung macrophages High Supported Q08380 3959 +ENSG00000108679 LGALS3BP lung pneumocytes Low Supported Q08380 3959 +ENSG00000108733 PEX12 bronchus respiratory epithelial cells Medium Enhanced O00623 5193 +ENSG00000108733 PEX12 lung macrophages Low Enhanced O00623 5193 +ENSG00000108733 PEX12 lung pneumocytes Medium Enhanced O00623 5193 +ENSG00000108784 NAGLU lung macrophages Low Supported P54802 4669 +ENSG00000108798 ABI3 lung macrophages Low Enhanced Q9P2A4 51225 +ENSG00000108799 EZH1 bronchus respiratory epithelial cells Medium Supported Q92800 2145 +ENSG00000108799 EZH1 lung macrophages Low Supported Q92800 2145 +ENSG00000108799 EZH1 lung pneumocytes Low Supported Q92800 2145 +ENSG00000108829 LRRC59 bronchus respiratory epithelial cells Medium Enhanced Q96AG4 55379 +ENSG00000108829 LRRC59 lung macrophages Low Enhanced Q96AG4 55379 +ENSG00000108846 ABCC3 bronchus respiratory epithelial cells Medium Enhanced O15438 8714 +ENSG00000108846 ABCC3 lung macrophages Low Enhanced O15438 8714 +ENSG00000108848 LUC7L3 bronchus respiratory epithelial cells High Enhanced O95232 51747 +ENSG00000108848 LUC7L3 lung macrophages Medium Enhanced O95232 51747 +ENSG00000108848 LUC7L3 lung pneumocytes High Enhanced O95232 51747 +ENSG00000108854 SMURF2 bronchus respiratory epithelial cells Low Enhanced Q9HAU4 64750 +ENSG00000108854 SMURF2 lung pneumocytes Low Enhanced Q9HAU4 64750 +ENSG00000108883 EFTUD2 bronchus respiratory epithelial cells High Supported Q15029 9343 +ENSG00000108883 EFTUD2 lung macrophages High Supported Q15029 9343 +ENSG00000108883 EFTUD2 lung pneumocytes Medium Supported Q15029 9343 +ENSG00000108984 MAP2K6 bronchus respiratory epithelial cells Low Enhanced P52564 5608 +ENSG00000108984 MAP2K6 lung macrophages Low Enhanced P52564 5608 +ENSG00000108984 MAP2K6 lung pneumocytes Low Enhanced P52564 5608 +ENSG00000109062 SLC9A3R1 bronchus respiratory epithelial cells Medium Enhanced O14745 9368 +ENSG00000109062 SLC9A3R1 lung macrophages Low Enhanced O14745 9368 +ENSG00000109072 VTN lung macrophages Low Supported P04004 7448 +ENSG00000109089 CDR2L bronchus respiratory epithelial cells Medium Enhanced Q86X02 30850 +ENSG00000109089 CDR2L lung macrophages Medium Enhanced Q86X02 30850 +ENSG00000109089 CDR2L lung pneumocytes Low Enhanced Q86X02 30850 +ENSG00000109270 LAMTOR3 bronchus respiratory epithelial cells Medium Supported Q9UHA4 8649 +ENSG00000109270 LAMTOR3 lung macrophages High Supported Q9UHA4 8649 +ENSG00000109270 LAMTOR3 lung pneumocytes Low Supported Q9UHA4 8649 +ENSG00000109320 NFKB1 bronchus respiratory epithelial cells Medium Enhanced P19838 4790 +ENSG00000109320 NFKB1 lung pneumocytes Low Enhanced P19838 4790 +ENSG00000109381 ELF2 bronchus respiratory epithelial cells High Enhanced Q15723 1998 +ENSG00000109381 ELF2 lung macrophages Medium Enhanced Q15723 1998 +ENSG00000109381 ELF2 lung pneumocytes High Enhanced Q15723 1998 +ENSG00000109458 GAB1 lung macrophages Low Enhanced Q13480 2549 +ENSG00000109458 GAB1 lung pneumocytes Low Enhanced Q13480 2549 +ENSG00000109472 CPE bronchus respiratory epithelial cells Low Supported P16870 1363 +ENSG00000109472 CPE lung macrophages Low Supported P16870 1363 +ENSG00000109519 GRPEL1 bronchus respiratory epithelial cells High Supported Q9HAV7 80273 +ENSG00000109519 GRPEL1 lung macrophages High Supported Q9HAV7 80273 +ENSG00000109519 GRPEL1 lung pneumocytes Medium Supported Q9HAV7 80273 +ENSG00000109534 GAR1 bronchus respiratory epithelial cells High Supported Q9NY12 54433 +ENSG00000109534 GAR1 lung pneumocytes High Supported Q9NY12 54433 +ENSG00000109586 GALNT7 bronchus respiratory epithelial cells High Enhanced Q86SF2 51809 +ENSG00000109586 GALNT7 lung macrophages Medium Enhanced Q86SF2 51809 +ENSG00000109586 GALNT7 lung pneumocytes Medium Enhanced Q86SF2 51809 +ENSG00000109610 SOD3 lung pneumocytes Medium Supported P08294 6649 +ENSG00000109670 FBXW7 bronchus respiratory epithelial cells High Supported Q969H0 55294 +ENSG00000109670 FBXW7 lung macrophages High Supported Q969H0 55294 +ENSG00000109670 FBXW7 lung pneumocytes High Supported Q969H0 55294 +ENSG00000109685 NSD2 bronchus respiratory epithelial cells Medium Enhanced O96028 7468 +ENSG00000109685 NSD2 lung macrophages Medium Enhanced O96028 7468 +ENSG00000109685 NSD2 lung pneumocytes Medium Enhanced O96028 7468 +ENSG00000109686 SH3D19 bronchus respiratory epithelial cells High Enhanced Q5HYK7 152503 +ENSG00000109686 SH3D19 lung macrophages Low Enhanced Q5HYK7 152503 +ENSG00000109686 SH3D19 lung pneumocytes Low Enhanced Q5HYK7 152503 +ENSG00000109689 STIM2 bronchus respiratory epithelial cells Medium Supported Q9P246 57620 +ENSG00000109689 STIM2 lung macrophages High Supported Q9P246 57620 +ENSG00000109689 STIM2 lung pneumocytes Medium Supported Q9P246 57620 +ENSG00000109787 KLF3 bronchus respiratory epithelial cells High Supported P57682 51274 +ENSG00000109787 KLF3 lung macrophages Low Supported P57682 51274 +ENSG00000109787 KLF3 lung pneumocytes Medium Supported P57682 51274 +ENSG00000109814 UGDH bronchus respiratory epithelial cells High Enhanced O60701 7358 +ENSG00000109861 CTSC bronchus respiratory epithelial cells Medium Enhanced P53634 1075 +ENSG00000109861 CTSC lung macrophages High Enhanced P53634 1075 +ENSG00000109920 FNBP4 bronchus respiratory epithelial cells Low Supported Q8N3X1 23360 +ENSG00000110031 LPXN lung macrophages Medium Supported O60711 9404 +ENSG00000110048 OSBP bronchus respiratory epithelial cells Medium Enhanced P22059 5007 +ENSG00000110048 OSBP lung macrophages Medium Enhanced P22059 5007 +ENSG00000110048 OSBP lung pneumocytes Medium Enhanced P22059 5007 +ENSG00000110063 DCPS bronchus respiratory epithelial cells High Supported Q96C86 28960 +ENSG00000110063 DCPS lung macrophages Low Supported Q96C86 28960 +ENSG00000110063 DCPS lung pneumocytes High Supported Q96C86 28960 +ENSG00000110075 PPP6R3 bronchus respiratory epithelial cells High Enhanced Q5H9R7 55291 +ENSG00000110075 PPP6R3 lung macrophages High Enhanced Q5H9R7 55291 +ENSG00000110075 PPP6R3 lung pneumocytes High Enhanced Q5H9R7 55291 +ENSG00000110090 CPT1A bronchus respiratory epithelial cells Medium Enhanced P50416 1374 +ENSG00000110090 CPT1A lung macrophages Medium Enhanced P50416 1374 +ENSG00000110104 CCDC86 bronchus respiratory epithelial cells Medium Enhanced Q9H6F5 79080 +ENSG00000110104 CCDC86 lung macrophages Low Enhanced Q9H6F5 79080 +ENSG00000110104 CCDC86 lung pneumocytes Low Enhanced Q9H6F5 79080 +ENSG00000110107 PRPF19 bronchus respiratory epithelial cells High Supported Q9UMS4 27339 +ENSG00000110107 PRPF19 lung macrophages Medium Supported Q9UMS4 27339 +ENSG00000110107 PRPF19 lung pneumocytes Medium Supported Q9UMS4 27339 +ENSG00000110330 BIRC2 lung macrophages High Supported Q13490 329 +ENSG00000110330 BIRC2 lung pneumocytes Medium Supported Q13490 329 +ENSG00000110395 CBL lung macrophages Low Enhanced P22681 867 +ENSG00000110435 PDHX bronchus respiratory epithelial cells High Enhanced O00330 8050 +ENSG00000110435 PDHX lung macrophages Medium Enhanced O00330 8050 +ENSG00000110435 PDHX lung pneumocytes Medium Enhanced O00330 8050 +ENSG00000110619 CARS bronchus respiratory epithelial cells High Enhanced NA NA +ENSG00000110619 CARS lung macrophages Low Enhanced NA NA +ENSG00000110619 CARS lung pneumocytes Medium Enhanced NA NA +ENSG00000110628 SLC22A18 bronchus respiratory epithelial cells Low Enhanced Q96BI1 5002 +ENSG00000110693 SOX6 lung macrophages Low Enhanced P35712 55553 +ENSG00000110768 GTF2H1 bronchus respiratory epithelial cells High Enhanced P32780 2965 +ENSG00000110768 GTF2H1 lung macrophages Medium Enhanced P32780 2965 +ENSG00000110768 GTF2H1 lung pneumocytes High Enhanced P32780 2965 +ENSG00000110801 PSMD9 lung macrophages High Enhanced O00233 5715 +ENSG00000110801 PSMD9 lung pneumocytes Medium Enhanced O00233 5715 +ENSG00000110844 PRPF40B bronchus respiratory epithelial cells Medium Enhanced Q6NWY9 25766 +ENSG00000110844 PRPF40B lung macrophages Medium Enhanced Q6NWY9 25766 +ENSG00000110844 PRPF40B lung pneumocytes Low Enhanced Q6NWY9 25766 +ENSG00000110934 BIN2 lung macrophages Medium Enhanced Q9UBW5 51411 +ENSG00000110955 ATP5B bronchus respiratory epithelial cells Medium Enhanced P06576 506 +ENSG00000110955 ATP5B lung macrophages Medium Enhanced P06576 506 +ENSG00000110955 ATP5B lung pneumocytes Medium Enhanced P06576 506 +ENSG00000110958 PTGES3 bronchus respiratory epithelial cells Medium Enhanced Q15185 10728 +ENSG00000110958 PTGES3 lung macrophages Medium Enhanced Q15185 10728 +ENSG00000110958 PTGES3 lung pneumocytes Low Enhanced Q15185 10728 +ENSG00000111057 KRT18 bronchus respiratory epithelial cells High Enhanced P05783 3875 +ENSG00000111057 KRT18 lung pneumocytes High Enhanced P05783 3875 +ENSG00000111142 METAP2 bronchus respiratory epithelial cells Medium Enhanced P50579 10988 +ENSG00000111142 METAP2 lung macrophages Medium Enhanced P50579 10988 +ENSG00000111142 METAP2 lung pneumocytes Medium Enhanced P50579 10988 +ENSG00000111144 LTA4H bronchus respiratory epithelial cells Medium Supported P09960 4048 +ENSG00000111144 LTA4H lung macrophages Medium Supported P09960 4048 +ENSG00000111144 LTA4H lung pneumocytes Low Supported P09960 4048 +ENSG00000111319 SCNN1A bronchus respiratory epithelial cells Medium Enhanced P37088 6337 +ENSG00000111319 SCNN1A lung macrophages Medium Enhanced P37088 6337 +ENSG00000111319 SCNN1A lung pneumocytes Low Enhanced P37088 6337 +ENSG00000111445 RFC5 bronchus respiratory epithelial cells Medium Supported P40937 5985 +ENSG00000111445 RFC5 lung macrophages Low Supported P40937 5985 +ENSG00000111602 TIMELESS bronchus respiratory epithelial cells Low Enhanced Q9UNS1 8914 +ENSG00000111605 CPSF6 bronchus respiratory epithelial cells High Supported Q16630 11052 +ENSG00000111605 CPSF6 lung macrophages Medium Supported Q16630 11052 +ENSG00000111605 CPSF6 lung pneumocytes High Supported Q16630 11052 +ENSG00000111640 GAPDH bronchus respiratory epithelial cells Medium Supported P04406 2597 +ENSG00000111640 GAPDH lung macrophages Medium Supported P04406 2597 +ENSG00000111640 GAPDH lung pneumocytes Medium Supported P04406 2597 +ENSG00000111641 NOP2 lung macrophages Low Supported P46087 4839 +ENSG00000111642 CHD4 bronchus respiratory epithelial cells High Supported Q14839 1108 +ENSG00000111642 CHD4 lung macrophages Medium Supported Q14839 1108 +ENSG00000111642 CHD4 lung pneumocytes Medium Supported Q14839 1108 +ENSG00000111652 COPS7A bronchus respiratory epithelial cells High Supported Q9UBW8 50813 +ENSG00000111652 COPS7A lung macrophages Low Supported Q9UBW8 50813 +ENSG00000111652 COPS7A lung pneumocytes Low Supported Q9UBW8 50813 +ENSG00000111676 ATN1 bronchus respiratory epithelial cells Medium Enhanced P54259 1822 +ENSG00000111679 PTPN6 lung macrophages Medium Enhanced P29350 5777 +ENSG00000111716 LDHB bronchus respiratory epithelial cells High Enhanced P07195 3945 +ENSG00000111716 LDHB lung macrophages Medium Enhanced P07195 3945 +ENSG00000111716 LDHB lung pneumocytes Low Enhanced P07195 3945 +ENSG00000111725 PRKAB1 bronchus respiratory epithelial cells High Enhanced Q9Y478 5564 +ENSG00000111725 PRKAB1 lung macrophages Medium Enhanced Q9Y478 5564 +ENSG00000111725 PRKAB1 lung pneumocytes Medium Enhanced Q9Y478 5564 +ENSG00000111726 CMAS bronchus respiratory epithelial cells High Supported Q8NFW8 55907 +ENSG00000111726 CMAS lung macrophages Medium Supported Q8NFW8 55907 +ENSG00000111726 CMAS lung pneumocytes Low Supported Q8NFW8 55907 +ENSG00000111786 SRSF9 bronchus respiratory epithelial cells High Enhanced Q13242 8683 +ENSG00000111786 SRSF9 lung macrophages Low Enhanced Q13242 8683 +ENSG00000111786 SRSF9 lung pneumocytes Low Enhanced Q13242 8683 +ENSG00000111790 FGFR1OP2 bronchus respiratory epithelial cells High Supported Q9NVK5 26127 +ENSG00000111790 FGFR1OP2 lung macrophages Medium Supported Q9NVK5 26127 +ENSG00000111790 FGFR1OP2 lung pneumocytes High Supported Q9NVK5 26127 +ENSG00000111801 BTN3A3 bronchus respiratory epithelial cells Medium Enhanced O00478 10384 +ENSG00000111801 BTN3A3 lung macrophages Medium Enhanced O00478 10384 +ENSG00000111801 BTN3A3 lung pneumocytes Medium Enhanced O00478 10384 +ENSG00000111802 TDP2 bronchus respiratory epithelial cells Low Enhanced O95551 51567 +ENSG00000111802 TDP2 lung macrophages Low Enhanced O95551 51567 +ENSG00000111834 RSPH4A bronchus respiratory epithelial cells High Enhanced Q5TD94 345895 +ENSG00000111845 PAK1IP1 bronchus respiratory epithelial cells High Supported Q9NWT1 55003 +ENSG00000111845 PAK1IP1 lung macrophages High Supported Q9NWT1 55003 +ENSG00000111845 PAK1IP1 lung pneumocytes High Supported Q9NWT1 55003 +ENSG00000111907 TPD52L1 bronchus respiratory epithelial cells Low Enhanced Q16890 7164 +ENSG00000111981 ULBP1 bronchus respiratory epithelial cells Low Enhanced Q9BZM6 80329 +ENSG00000111981 ULBP1 lung macrophages Low Enhanced Q9BZM6 80329 +ENSG00000112039 FANCE bronchus respiratory epithelial cells High Enhanced Q9HB96 2178 +ENSG00000112039 FANCE lung macrophages High Enhanced Q9HB96 2178 +ENSG00000112039 FANCE lung pneumocytes High Enhanced Q9HB96 2178 +ENSG00000112081 SRSF3 bronchus respiratory epithelial cells High Supported P84103 6428 +ENSG00000112081 SRSF3 lung macrophages High Supported P84103 6428 +ENSG00000112081 SRSF3 lung pneumocytes High Supported P84103 6428 +ENSG00000112096 SOD2 bronchus respiratory epithelial cells Medium Supported P04179 6648 +ENSG00000112096 SOD2 lung macrophages Medium Supported P04179 6648 +ENSG00000112096 SOD2 lung pneumocytes Medium Supported P04179 6648 +ENSG00000112110 MRPL18 bronchus respiratory epithelial cells Medium Enhanced Q9H0U6 29074 +ENSG00000112110 MRPL18 lung macrophages Medium Enhanced Q9H0U6 29074 +ENSG00000112137 PHACTR1 bronchus respiratory epithelial cells Low Enhanced H0Y3U1 NA +ENSG00000112137 PHACTR1 lung macrophages Low Enhanced H0Y3U1 NA +ENSG00000112137 PHACTR1 lung pneumocytes Medium Enhanced H0Y3U1 NA +ENSG00000112149 CD83 lung macrophages Medium Enhanced Q01151 9308 +ENSG00000112182 BACH2 bronchus respiratory epithelial cells Low Enhanced Q9BYV9 60468 +ENSG00000112182 BACH2 lung macrophages Low Enhanced Q9BYV9 60468 +ENSG00000112183 RBM24 bronchus respiratory epithelial cells Low Enhanced Q9BX46 221662 +ENSG00000112186 CAP2 bronchus respiratory epithelial cells Medium Enhanced P40123 10486 +ENSG00000112208 BAG2 bronchus respiratory epithelial cells Low Enhanced O95816 9532 +ENSG00000112208 BAG2 lung macrophages Low Enhanced O95816 9532 +ENSG00000112208 BAG2 lung pneumocytes Low Enhanced O95816 9532 +ENSG00000112210 RAB23 bronchus respiratory epithelial cells High Enhanced Q9ULC3 51715 +ENSG00000112210 RAB23 lung macrophages Medium Enhanced Q9ULC3 51715 +ENSG00000112210 RAB23 lung pneumocytes Low Enhanced Q9ULC3 51715 +ENSG00000112232 KHDRBS2 bronchus respiratory epithelial cells Medium Supported Q5VWX1 202559 +ENSG00000112232 KHDRBS2 lung pneumocytes Low Supported Q5VWX1 202559 +ENSG00000112249 ASCC3 bronchus respiratory epithelial cells High Enhanced Q8N3C0 10973 +ENSG00000112249 ASCC3 lung macrophages Medium Enhanced Q8N3C0 10973 +ENSG00000112249 ASCC3 lung pneumocytes Medium Enhanced Q8N3C0 10973 +ENSG00000112276 BVES bronchus respiratory epithelial cells Low Enhanced Q8NE79 11149 +ENSG00000112276 BVES lung pneumocytes Low Enhanced Q8NE79 11149 +ENSG00000112294 ALDH5A1 bronchus respiratory epithelial cells Medium Enhanced P51649 7915 +ENSG00000112294 ALDH5A1 lung macrophages Low Enhanced P51649 7915 +ENSG00000112308 C6orf62 bronchus respiratory epithelial cells Medium Enhanced Q9GZU0 81688 +ENSG00000112308 C6orf62 lung macrophages Medium Enhanced Q9GZU0 81688 +ENSG00000112308 C6orf62 lung pneumocytes Low Enhanced Q9GZU0 81688 +ENSG00000112312 GMNN bronchus respiratory epithelial cells Low Enhanced O75496 51053 +ENSG00000112312 GMNN lung macrophages Low Enhanced O75496 51053 +ENSG00000112319 EYA4 bronchus respiratory epithelial cells Medium Enhanced O95677 2070 +ENSG00000112319 EYA4 lung macrophages Low Enhanced O95677 2070 +ENSG00000112531 QKI lung macrophages Medium Enhanced Q96PU8 9444 +ENSG00000112531 QKI lung pneumocytes Low Enhanced Q96PU8 9444 +ENSG00000112578 BYSL bronchus respiratory epithelial cells Medium Enhanced Q13895 705 +ENSG00000112578 BYSL lung macrophages Low Enhanced Q13895 705 +ENSG00000112658 SRF bronchus respiratory epithelial cells High Supported P11831 6722 +ENSG00000112658 SRF lung macrophages Medium Supported P11831 6722 +ENSG00000112658 SRF lung pneumocytes Medium Supported P11831 6722 +ENSG00000112667 DNPH1 bronchus respiratory epithelial cells Medium Enhanced O43598 10591 +ENSG00000112667 DNPH1 lung macrophages High Enhanced O43598 10591 +ENSG00000112699 GMDS bronchus respiratory epithelial cells Medium Enhanced O60547 2762 +ENSG00000112699 GMDS lung macrophages Medium Enhanced O60547 2762 +ENSG00000112699 GMDS lung pneumocytes Low Enhanced O60547 2762 +ENSG00000112715 VEGFA bronchus respiratory epithelial cells High Supported P15692 7422 +ENSG00000112715 VEGFA lung macrophages High Supported P15692 7422 +ENSG00000112715 VEGFA lung pneumocytes Medium Supported P15692 7422 +ENSG00000112742 TTK bronchus respiratory epithelial cells Low Enhanced P33981 7272 +ENSG00000112742 TTK lung macrophages Low Enhanced P33981 7272 +ENSG00000112742 TTK lung pneumocytes Low Enhanced P33981 7272 +ENSG00000112796 ENPP5 bronchus respiratory epithelial cells Low Enhanced Q9UJA9 59084 +ENSG00000112796 ENPP5 lung macrophages Low Enhanced Q9UJA9 59084 +ENSG00000112852 PCDHB2 lung macrophages Low Enhanced Q9Y5E7 56133 +ENSG00000112874 NUDT12 bronchus respiratory epithelial cells Medium Supported Q9BQG2 83594 +ENSG00000112874 NUDT12 lung macrophages High Supported Q9BQG2 83594 +ENSG00000112874 NUDT12 lung pneumocytes Medium Supported Q9BQG2 83594 +ENSG00000112893 MAN2A1 bronchus respiratory epithelial cells Medium Enhanced Q16706 4124 +ENSG00000112893 MAN2A1 lung macrophages Low Enhanced Q16706 4124 +ENSG00000112941 PAPD7 bronchus respiratory epithelial cells High Enhanced Q5XG87 11044 +ENSG00000112941 PAPD7 lung macrophages High Enhanced Q5XG87 11044 +ENSG00000112941 PAPD7 lung pneumocytes High Enhanced Q5XG87 11044 +ENSG00000112964 GHR bronchus respiratory epithelial cells Low Enhanced P10912 2690 +ENSG00000112983 BRD8 bronchus respiratory epithelial cells Medium Supported Q9H0E9 10902 +ENSG00000112983 BRD8 lung macrophages High Supported Q9H0E9 10902 +ENSG00000112983 BRD8 lung pneumocytes Low Supported Q9H0E9 10902 +ENSG00000112992 NNT bronchus respiratory epithelial cells Medium Enhanced Q13423 23530 +ENSG00000112992 NNT lung macrophages High Enhanced Q13423 23530 +ENSG00000112996 MRPS30 bronchus respiratory epithelial cells High Enhanced Q9NP92 10884 +ENSG00000112996 MRPS30 lung macrophages High Enhanced Q9NP92 10884 +ENSG00000112996 MRPS30 lung pneumocytes Low Enhanced Q9NP92 10884 +ENSG00000113013 HSPA9 bronchus respiratory epithelial cells High Enhanced P38646 3313 +ENSG00000113013 HSPA9 lung macrophages High Enhanced P38646 3313 +ENSG00000113013 HSPA9 lung pneumocytes High Enhanced P38646 3313 +ENSG00000113140 SPARC lung macrophages Medium Supported P09486 6678 +ENSG00000113140 SPARC lung pneumocytes Low Supported P09486 6678 +ENSG00000113141 IK bronchus respiratory epithelial cells High Supported Q13123 3550 +ENSG00000113141 IK lung macrophages High Supported Q13123 3550 +ENSG00000113141 IK lung pneumocytes High Supported Q13123 3550 +ENSG00000113273 ARSB bronchus respiratory epithelial cells Medium Enhanced P15848 411 +ENSG00000113273 ARSB lung macrophages Medium Enhanced P15848 411 +ENSG00000113273 ARSB lung pneumocytes Low Enhanced P15848 411 +ENSG00000113282 CLINT1 bronchus respiratory epithelial cells High Supported Q14677 9685 +ENSG00000113282 CLINT1 lung macrophages Medium Supported Q14677 9685 +ENSG00000113282 CLINT1 lung pneumocytes Medium Supported Q14677 9685 +ENSG00000113328 CCNG1 bronchus respiratory epithelial cells High Supported P51959 900 +ENSG00000113328 CCNG1 lung pneumocytes Medium Supported P51959 900 +ENSG00000113356 POLR3G bronchus respiratory epithelial cells Low Enhanced O15318 10622 +ENSG00000113361 CDH6 bronchus respiratory epithelial cells Low Enhanced P55285 1004 +ENSG00000113361 CDH6 lung macrophages Medium Enhanced P55285 1004 +ENSG00000113368 LMNB1 bronchus respiratory epithelial cells High Supported P20700 4001 +ENSG00000113368 LMNB1 lung macrophages Medium Supported P20700 4001 +ENSG00000113368 LMNB1 lung pneumocytes High Supported P20700 4001 +ENSG00000113387 SUB1 bronchus respiratory epithelial cells Medium Supported P53999 10923 +ENSG00000113387 SUB1 lung macrophages Low Supported P53999 10923 +ENSG00000113387 SUB1 lung pneumocytes Medium Supported P53999 10923 +ENSG00000113522 RAD50 bronchus respiratory epithelial cells High Enhanced Q92878 10111 +ENSG00000113522 RAD50 lung macrophages Low Enhanced Q92878 10111 +ENSG00000113522 RAD50 lung pneumocytes Medium Enhanced Q92878 10111 +ENSG00000113569 NUP155 bronchus respiratory epithelial cells Medium Enhanced O75694 9631 +ENSG00000113569 NUP155 lung macrophages Low Enhanced O75694 9631 +ENSG00000113580 NR3C1 bronchus respiratory epithelial cells High Supported P04150 2908 +ENSG00000113580 NR3C1 lung macrophages High Supported P04150 2908 +ENSG00000113580 NR3C1 lung pneumocytes High Supported P04150 2908 +ENSG00000113593 PPWD1 bronchus respiratory epithelial cells High Enhanced Q96BP3 23398 +ENSG00000113593 PPWD1 lung macrophages Medium Enhanced Q96BP3 23398 +ENSG00000113593 PPWD1 lung pneumocytes Medium Enhanced Q96BP3 23398 +ENSG00000113648 H2AFY bronchus respiratory epithelial cells Medium Supported O75367 9555 +ENSG00000113648 H2AFY lung macrophages High Supported O75367 9555 +ENSG00000113648 H2AFY lung pneumocytes High Supported O75367 9555 +ENSG00000113649 TCERG1 bronchus respiratory epithelial cells Medium Enhanced O14776 10915 +ENSG00000113649 TCERG1 lung macrophages Medium Enhanced O14776 10915 +ENSG00000113649 TCERG1 lung pneumocytes Medium Enhanced O14776 10915 +ENSG00000113719 ERGIC1 bronchus respiratory epithelial cells Medium Enhanced Q969X5 57222 +ENSG00000113719 ERGIC1 lung macrophages Medium Enhanced Q969X5 57222 +ENSG00000113719 ERGIC1 lung pneumocytes Medium Enhanced Q969X5 57222 +ENSG00000113734 BNIP1 lung macrophages Medium Enhanced Q12981 662 +ENSG00000113916 BCL6 bronchus respiratory epithelial cells High Enhanced P41182 604 +ENSG00000114030 KPNA1 bronchus respiratory epithelial cells Medium Enhanced P52294 3836 +ENSG00000114030 KPNA1 lung macrophages Low Enhanced P52294 3836 +ENSG00000114030 KPNA1 lung pneumocytes Low Enhanced P52294 3836 +ENSG00000114054 PCCB bronchus respiratory epithelial cells Medium Enhanced P05166 5096 +ENSG00000114054 PCCB lung macrophages Medium Enhanced P05166 5096 +ENSG00000114107 CEP70 bronchus respiratory epithelial cells Medium Enhanced Q8NHQ1 80321 +ENSG00000114107 CEP70 lung macrophages Medium Enhanced Q8NHQ1 80321 +ENSG00000114107 CEP70 lung pneumocytes Medium Enhanced Q8NHQ1 80321 +ENSG00000114126 TFDP2 bronchus respiratory epithelial cells High Supported Q14188 7029 +ENSG00000114126 TFDP2 lung macrophages High Supported Q14188 7029 +ENSG00000114126 TFDP2 lung pneumocytes High Supported Q14188 7029 +ENSG00000114166 KAT2B bronchus respiratory epithelial cells Medium Supported Q92831 8850 +ENSG00000114166 KAT2B lung macrophages Medium Supported Q92831 8850 +ENSG00000114166 KAT2B lung pneumocytes Medium Supported Q92831 8850 +ENSG00000114331 ACAP2 bronchus respiratory epithelial cells Medium Supported Q15057 23527 +ENSG00000114331 ACAP2 lung macrophages High Supported Q15057 23527 +ENSG00000114331 ACAP2 lung pneumocytes High Supported Q15057 23527 +ENSG00000114439 BBX bronchus respiratory epithelial cells Medium Enhanced Q8WY36 56987 +ENSG00000114439 BBX lung macrophages Low Enhanced Q8WY36 56987 +ENSG00000114439 BBX lung pneumocytes Medium Enhanced Q8WY36 56987 +ENSG00000114446 IFT57 bronchus respiratory epithelial cells High Supported Q9NWB7 55081 +ENSG00000114446 IFT57 lung macrophages High Supported Q9NWB7 55081 +ENSG00000114446 IFT57 lung pneumocytes Low Supported Q9NWB7 55081 +ENSG00000114450 GNB4 bronchus respiratory epithelial cells Medium Enhanced Q9HAV0 59345 +ENSG00000114450 GNB4 lung macrophages Medium Enhanced Q9HAV0 59345 +ENSG00000114450 GNB4 lung pneumocytes Medium Enhanced Q9HAV0 59345 +ENSG00000114473 IQCG bronchus respiratory epithelial cells High Enhanced Q9H095 84223 +ENSG00000114480 GBE1 bronchus respiratory epithelial cells Medium Enhanced Q04446 2632 +ENSG00000114480 GBE1 lung macrophages Medium Enhanced Q04446 2632 +ENSG00000114480 GBE1 lung pneumocytes Medium Enhanced Q04446 2632 +ENSG00000114503 NCBP2 bronchus respiratory epithelial cells High Supported P52298 22916 +ENSG00000114503 NCBP2 lung macrophages Medium Supported P52298 22916 +ENSG00000114503 NCBP2 lung pneumocytes Medium Supported P52298 22916 +ENSG00000114745 GORASP1 bronchus respiratory epithelial cells Medium Enhanced Q9BQQ3 64689 +ENSG00000114745 GORASP1 lung macrophages Medium Enhanced Q9BQQ3 64689 +ENSG00000114745 GORASP1 lung pneumocytes Medium Enhanced Q9BQQ3 64689 +ENSG00000114757 PEX5L bronchus respiratory epithelial cells Medium Enhanced Q8IYB4 51555 +ENSG00000114757 PEX5L lung macrophages Medium Enhanced Q8IYB4 51555 +ENSG00000114779 ABHD14B bronchus respiratory epithelial cells Medium Supported Q96IU4 84836 +ENSG00000114779 ABHD14B lung macrophages High Supported Q96IU4 84836 +ENSG00000114779 ABHD14B lung pneumocytes Medium Supported Q96IU4 84836 +ENSG00000114861 FOXP1 bronchus respiratory epithelial cells High Supported Q9H334 27086 +ENSG00000114861 FOXP1 lung macrophages Medium Supported Q9H334 27086 +ENSG00000114861 FOXP1 lung pneumocytes Medium Supported Q9H334 27086 +ENSG00000114902 SPCS1 bronchus respiratory epithelial cells Medium Supported Q9Y6A9 28972 +ENSG00000114902 SPCS1 lung macrophages Low Supported Q9Y6A9 28972 +ENSG00000114942 EEF1B2 bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000114942 EEF1B2 lung macrophages Medium Supported NA NA +ENSG00000114942 EEF1B2 lung pneumocytes Medium Supported NA NA +ENSG00000114978 MOB1A bronchus respiratory epithelial cells Medium Supported Q9H8S9 55233 +ENSG00000114978 MOB1A lung macrophages Medium Supported Q9H8S9 55233 +ENSG00000114978 MOB1A lung pneumocytes Low Supported Q9H8S9 55233 +ENSG00000115042 FAHD2A bronchus respiratory epithelial cells High Enhanced Q96GK7 51011 +ENSG00000115042 FAHD2A lung macrophages Low Enhanced Q96GK7 51011 +ENSG00000115053 NCL bronchus respiratory epithelial cells High Supported P19338 4691 +ENSG00000115053 NCL lung macrophages Medium Supported P19338 4691 +ENSG00000115053 NCL lung pneumocytes High Supported P19338 4691 +ENSG00000115085 ZAP70 lung macrophages Low Enhanced P43403 7535 +ENSG00000115128 SF3B6 bronchus respiratory epithelial cells Low Enhanced Q9Y3B4 51639 +ENSG00000115128 SF3B6 lung pneumocytes Low Enhanced Q9Y3B4 51639 +ENSG00000115129 TP53I3 bronchus respiratory epithelial cells Medium Enhanced Q53FA7 9540 +ENSG00000115129 TP53I3 lung macrophages Medium Enhanced Q53FA7 9540 +ENSG00000115129 TP53I3 lung pneumocytes Low Enhanced Q53FA7 9540 +ENSG00000115145 STAM2 bronchus respiratory epithelial cells High Enhanced O75886 10254 +ENSG00000115145 STAM2 lung macrophages High Enhanced O75886 10254 +ENSG00000115145 STAM2 lung pneumocytes Low Enhanced O75886 10254 +ENSG00000115159 GPD2 bronchus respiratory epithelial cells High Enhanced P43304 2820 +ENSG00000115159 GPD2 lung macrophages High Enhanced P43304 2820 +ENSG00000115159 GPD2 lung pneumocytes High Enhanced P43304 2820 +ENSG00000115216 NRBP1 bronchus respiratory epithelial cells Medium Supported Q9UHY1 29959 +ENSG00000115216 NRBP1 lung macrophages Medium Supported Q9UHY1 29959 +ENSG00000115216 NRBP1 lung pneumocytes Low Supported Q9UHY1 29959 +ENSG00000115234 SNX17 bronchus respiratory epithelial cells Medium Supported Q15036 9784 +ENSG00000115234 SNX17 lung macrophages Low Supported Q15036 9784 +ENSG00000115234 SNX17 lung pneumocytes Low Supported Q15036 9784 +ENSG00000115241 PPM1G bronchus respiratory epithelial cells Medium Enhanced O15355 5496 +ENSG00000115241 PPM1G lung macrophages Medium Enhanced O15355 5496 +ENSG00000115241 PPM1G lung pneumocytes Medium Enhanced O15355 5496 +ENSG00000115255 REEP6 bronchus respiratory epithelial cells Medium Enhanced Q96HR9 92840 +ENSG00000115255 REEP6 lung macrophages Medium Enhanced Q96HR9 92840 +ENSG00000115255 REEP6 lung pneumocytes Low Enhanced Q96HR9 92840 +ENSG00000115268 RPS15 bronchus respiratory epithelial cells High Enhanced P62841 6209 +ENSG00000115268 RPS15 lung macrophages Low Enhanced P62841 6209 +ENSG00000115268 RPS15 lung pneumocytes Low Enhanced P62841 6209 +ENSG00000115271 GCA lung macrophages Medium Enhanced P28676 25801 +ENSG00000115289 PCGF1 bronchus respiratory epithelial cells High Enhanced Q9BSM1 84759 +ENSG00000115289 PCGF1 lung macrophages Low Enhanced Q9BSM1 84759 +ENSG00000115289 PCGF1 lung pneumocytes Low Enhanced Q9BSM1 84759 +ENSG00000115306 SPTBN1 bronchus respiratory epithelial cells High Supported Q01082 6711 +ENSG00000115306 SPTBN1 lung macrophages Low Supported Q01082 6711 +ENSG00000115306 SPTBN1 lung pneumocytes High Supported Q01082 6711 +ENSG00000115339 GALNT3 bronchus respiratory epithelial cells High Enhanced Q14435 2591 +ENSG00000115339 GALNT3 lung macrophages Medium Enhanced Q14435 2591 +ENSG00000115339 GALNT3 lung pneumocytes Medium Enhanced Q14435 2591 +ENSG00000115353 TACR1 bronchus respiratory epithelial cells Medium Enhanced P25103 6869 +ENSG00000115355 CCDC88A lung macrophages Low Enhanced Q3V6T2 55704 +ENSG00000115355 CCDC88A lung pneumocytes Low Enhanced Q3V6T2 55704 +ENSG00000115361 ACADL bronchus respiratory epithelial cells Low Enhanced P28330 33 +ENSG00000115361 ACADL lung macrophages Medium Enhanced P28330 33 +ENSG00000115392 FANCL bronchus respiratory epithelial cells Medium Supported Q9NW38 55120 +ENSG00000115392 FANCL lung macrophages Medium Supported Q9NW38 55120 +ENSG00000115392 FANCL lung pneumocytes Medium Supported Q9NW38 55120 +ENSG00000115414 FN1 bronchus respiratory epithelial cells Low Enhanced P02751 2335 +ENSG00000115414 FN1 lung macrophages Low Enhanced P02751 2335 +ENSG00000115419 GLS lung macrophages Medium Enhanced O94925 2744 +ENSG00000115423 DNAH6 bronchus respiratory epithelial cells Medium Enhanced Q9C0G6 1768 +ENSG00000115425 PECR bronchus respiratory epithelial cells High Enhanced Q9BY49 55825 +ENSG00000115425 PECR lung macrophages High Enhanced Q9BY49 55825 +ENSG00000115425 PECR lung pneumocytes Medium Enhanced Q9BY49 55825 +ENSG00000115468 EFHD1 bronchus respiratory epithelial cells Low Enhanced Q9BUP0 80303 +ENSG00000115468 EFHD1 lung macrophages Medium Enhanced Q9BUP0 80303 +ENSG00000115484 CCT4 bronchus respiratory epithelial cells Medium Enhanced P50991 10575 +ENSG00000115504 EHBP1 bronchus respiratory epithelial cells Medium Enhanced Q8NDI1 23301 +ENSG00000115504 EHBP1 lung macrophages Medium Enhanced Q8NDI1 23301 +ENSG00000115541 HSPE1 bronchus respiratory epithelial cells High Supported P61604 3336 +ENSG00000115541 HSPE1 lung macrophages High Supported P61604 3336 +ENSG00000115541 HSPE1 lung pneumocytes High Supported P61604 3336 +ENSG00000115556 PLCD4 bronchus respiratory epithelial cells Low Enhanced Q9BRC7 84812 +ENSG00000115561 CHMP3 bronchus respiratory epithelial cells High Supported Q9Y3E7 100526767; 51652 +ENSG00000115561 CHMP3 lung macrophages High Supported Q9Y3E7 100526767; 51652 +ENSG00000115561 CHMP3 lung pneumocytes Low Supported Q9Y3E7 100526767; 51652 +ENSG00000115607 IL18RAP lung macrophages Low Enhanced O95256 8807 +ENSG00000115641 FHL2 lung macrophages Low Enhanced Q14192 2274 +ENSG00000115677 HDLBP bronchus respiratory epithelial cells Low Supported Q00341 3069 +ENSG00000115677 HDLBP lung macrophages Low Supported Q00341 3069 +ENSG00000115677 HDLBP lung pneumocytes Low Supported Q00341 3069 +ENSG00000115685 PPP1R7 bronchus respiratory epithelial cells Medium Supported Q15435 5510 +ENSG00000115685 PPP1R7 lung macrophages Low Supported Q15435 5510 +ENSG00000115685 PPP1R7 lung pneumocytes Low Supported Q15435 5510 +ENSG00000115806 GORASP2 bronchus respiratory epithelial cells High Enhanced Q9H8Y8 26003 +ENSG00000115806 GORASP2 lung macrophages Low Enhanced Q9H8Y8 26003 +ENSG00000115806 GORASP2 lung pneumocytes Low Enhanced Q9H8Y8 26003 +ENSG00000115840 SLC25A12 bronchus respiratory epithelial cells Medium Enhanced O75746 8604 +ENSG00000115840 SLC25A12 lung macrophages Medium Enhanced O75746 8604 +ENSG00000115840 SLC25A12 lung pneumocytes Low Enhanced O75746 8604 +ENSG00000115866 DARS bronchus respiratory epithelial cells Medium Enhanced P14868 1615 +ENSG00000115866 DARS lung macrophages Medium Enhanced P14868 1615 +ENSG00000115866 DARS lung pneumocytes Medium Enhanced P14868 1615 +ENSG00000115875 SRSF7 bronchus respiratory epithelial cells Medium Enhanced Q16629 6432 +ENSG00000115875 SRSF7 lung macrophages Medium Enhanced Q16629 6432 +ENSG00000115875 SRSF7 lung pneumocytes Medium Enhanced Q16629 6432 +ENSG00000115896 PLCL1 bronchus respiratory epithelial cells Medium Enhanced Q15111 5334 +ENSG00000115896 PLCL1 lung macrophages Medium Enhanced Q15111 5334 +ENSG00000115896 PLCL1 lung pneumocytes Low Enhanced Q15111 5334 +ENSG00000115919 KYNU bronchus respiratory epithelial cells Low Enhanced Q16719 8942 +ENSG00000115919 KYNU lung macrophages High Enhanced Q16719 8942 +ENSG00000115919 KYNU lung pneumocytes Low Enhanced Q16719 8942 +ENSG00000115935 WIPF1 lung macrophages Low Enhanced O43516 7456 +ENSG00000115942 ORC2 lung macrophages Low Enhanced Q13416 4999 +ENSG00000115956 PLEK lung pneumocytes Low Enhanced P08567 5341 +ENSG00000115966 ATF2 bronchus respiratory epithelial cells Medium Supported P15336 1386 +ENSG00000115966 ATF2 lung macrophages Medium Supported P15336 1386 +ENSG00000115966 ATF2 lung pneumocytes Medium Supported P15336 1386 +ENSG00000116030 SUMO1 bronchus respiratory epithelial cells High Supported P63165 7341 +ENSG00000116030 SUMO1 lung macrophages High Supported P63165 7341 +ENSG00000116030 SUMO1 lung pneumocytes High Supported P63165 7341 +ENSG00000116039 ATP6V1B1 lung macrophages Medium Enhanced P15313 525 +ENSG00000116044 NFE2L2 bronchus respiratory epithelial cells Medium Enhanced Q16236 4780 +ENSG00000116044 NFE2L2 lung macrophages Medium Enhanced Q16236 4780 +ENSG00000116044 NFE2L2 lung pneumocytes Medium Enhanced Q16236 4780 +ENSG00000116062 MSH6 bronchus respiratory epithelial cells High Enhanced P52701 2956 +ENSG00000116062 MSH6 lung macrophages High Enhanced P52701 2956 +ENSG00000116062 MSH6 lung pneumocytes High Enhanced P52701 2956 +ENSG00000116106 EPHA4 lung pneumocytes Low Enhanced P54764 2043 +ENSG00000116120 FARSB bronchus respiratory epithelial cells Low Enhanced Q9NSD9 10056 +ENSG00000116127 ALMS1 lung macrophages Low Enhanced Q8TCU4 7840 +ENSG00000116128 BCL9 bronchus respiratory epithelial cells Medium Enhanced O00512 607 +ENSG00000116128 BCL9 lung pneumocytes Medium Enhanced O00512 607 +ENSG00000116171 SCP2 bronchus respiratory epithelial cells Medium Supported P22307 6342 +ENSG00000116171 SCP2 lung macrophages Medium Supported P22307 6342 +ENSG00000116171 SCP2 lung pneumocytes Medium Supported P22307 6342 +ENSG00000116191 RALGPS2 bronchus respiratory epithelial cells Low Enhanced Q86X27 55103 +ENSG00000116191 RALGPS2 lung macrophages Low Enhanced Q86X27 55103 +ENSG00000116221 MRPL37 bronchus respiratory epithelial cells Medium Enhanced Q9BZE1 51253 +ENSG00000116221 MRPL37 lung macrophages Medium Enhanced Q9BZE1 51253 +ENSG00000116221 MRPL37 lung pneumocytes Low Enhanced Q9BZE1 51253 +ENSG00000116288 PARK7 bronchus respiratory epithelial cells Medium Enhanced Q99497 11315 +ENSG00000116288 PARK7 lung macrophages Medium Enhanced Q99497 11315 +ENSG00000116288 PARK7 lung pneumocytes High Enhanced Q99497 11315 +ENSG00000116299 KIAA1324 bronchus respiratory epithelial cells Medium Enhanced Q6UXG2 57535 +ENSG00000116299 KIAA1324 lung macrophages Low Enhanced Q6UXG2 57535 +ENSG00000116350 SRSF4 bronchus respiratory epithelial cells High Supported Q08170 6429 +ENSG00000116350 SRSF4 lung macrophages High Supported Q08170 6429 +ENSG00000116350 SRSF4 lung pneumocytes Medium Supported Q08170 6429 +ENSG00000116353 MECR bronchus respiratory epithelial cells Medium Enhanced Q9BV79 51102 +ENSG00000116353 MECR lung macrophages Medium Enhanced Q9BV79 51102 +ENSG00000116353 MECR lung pneumocytes Medium Enhanced Q9BV79 51102 +ENSG00000116459 ATP5F1 bronchus respiratory epithelial cells Medium Enhanced P24539 515 +ENSG00000116459 ATP5F1 lung macrophages Low Enhanced P24539 515 +ENSG00000116478 HDAC1 bronchus respiratory epithelial cells High Enhanced Q13547 3065 +ENSG00000116478 HDAC1 lung macrophages Medium Enhanced Q13547 3065 +ENSG00000116478 HDAC1 lung pneumocytes Medium Enhanced Q13547 3065 +ENSG00000116560 SFPQ bronchus respiratory epithelial cells High Enhanced P23246 6421 +ENSG00000116560 SFPQ lung macrophages High Enhanced P23246 6421 +ENSG00000116560 SFPQ lung pneumocytes High Enhanced P23246 6421 +ENSG00000116604 MEF2D bronchus respiratory epithelial cells High Enhanced Q14814 4209 +ENSG00000116604 MEF2D lung macrophages High Enhanced Q14814 4209 +ENSG00000116604 MEF2D lung pneumocytes High Enhanced Q14814 4209 +ENSG00000116668 SWT1 bronchus respiratory epithelial cells Medium Enhanced Q5T5J6 54823 +ENSG00000116668 SWT1 lung macrophages Medium Enhanced Q5T5J6 54823 +ENSG00000116668 SWT1 lung pneumocytes Medium Enhanced Q5T5J6 54823 +ENSG00000116698 SMG7 bronchus respiratory epithelial cells Medium Supported Q92540 9887 +ENSG00000116698 SMG7 lung macrophages Medium Supported Q92540 9887 +ENSG00000116701 NCF2 lung macrophages High Enhanced P19878 4688 +ENSG00000116748 AMPD1 lung macrophages Low Enhanced P23109 270 +ENSG00000116752 BCAS2 bronchus respiratory epithelial cells Medium Enhanced O75934 10286 +ENSG00000116752 BCAS2 lung macrophages Medium Enhanced O75934 10286 +ENSG00000116752 BCAS2 lung pneumocytes Low Enhanced O75934 10286 +ENSG00000116754 SRSF11 bronchus respiratory epithelial cells High Supported Q05519 9295 +ENSG00000116754 SRSF11 lung macrophages High Supported Q05519 9295 +ENSG00000116754 SRSF11 lung pneumocytes High Supported Q05519 9295 +ENSG00000116761 CTH lung macrophages Low Enhanced P32929 1491 +ENSG00000116761 CTH lung pneumocytes Low Enhanced P32929 1491 +ENSG00000116771 AGMAT bronchus respiratory epithelial cells Low Enhanced Q9BSE5 79814 +ENSG00000116771 AGMAT lung macrophages Medium Enhanced Q9BSE5 79814 +ENSG00000116833 NR5A2 bronchus respiratory epithelial cells High Supported O00482 2494 +ENSG00000116833 NR5A2 lung macrophages High Supported O00482 2494 +ENSG00000116833 NR5A2 lung pneumocytes High Supported O00482 2494 +ENSG00000116874 WARS2 bronchus respiratory epithelial cells High Enhanced Q9UGM6 10352 +ENSG00000116874 WARS2 lung macrophages Medium Enhanced Q9UGM6 10352 +ENSG00000116874 WARS2 lung pneumocytes Low Enhanced Q9UGM6 10352 +ENSG00000116898 MRPS15 bronchus respiratory epithelial cells Medium Enhanced P82914 64960 +ENSG00000116898 MRPS15 lung macrophages Low Enhanced P82914 64960 +ENSG00000116898 MRPS15 lung pneumocytes Low Enhanced P82914 64960 +ENSG00000116922 C1orf109 bronchus respiratory epithelial cells Medium Supported Q9NX04 54955 +ENSG00000116922 C1orf109 lung macrophages Medium Supported Q9NX04 54955 +ENSG00000116954 RRAGC bronchus respiratory epithelial cells High Enhanced Q9HB90 64121 +ENSG00000116954 RRAGC lung macrophages Medium Enhanced Q9HB90 64121 +ENSG00000116954 RRAGC lung pneumocytes Medium Enhanced Q9HB90 64121 +ENSG00000116981 NT5C1A lung pneumocytes Low Supported Q9BXI3 84618 +ENSG00000117036 ETV3 bronchus respiratory epithelial cells Medium Supported P41162 2117 +ENSG00000117036 ETV3 lung macrophages Medium Supported P41162 2117 +ENSG00000117036 ETV3 lung pneumocytes Medium Supported P41162 2117 +ENSG00000117054 ACADM bronchus respiratory epithelial cells High Enhanced P11310 34 +ENSG00000117054 ACADM lung macrophages Medium Enhanced P11310 34 +ENSG00000117054 ACADM lung pneumocytes Low Enhanced P11310 34 +ENSG00000117118 SDHB bronchus respiratory epithelial cells High Enhanced P21912 6390 +ENSG00000117118 SDHB lung macrophages High Enhanced P21912 6390 +ENSG00000117118 SDHB lung pneumocytes Low Enhanced P21912 6390 +ENSG00000117139 KDM5B bronchus respiratory epithelial cells Low Enhanced Q9UGL1 10765 +ENSG00000117139 KDM5B lung pneumocytes Low Enhanced Q9UGL1 10765 +ENSG00000117305 HMGCL bronchus respiratory epithelial cells Medium Enhanced P35914 3155 +ENSG00000117305 HMGCL lung macrophages High Enhanced P35914 3155 +ENSG00000117335 CD46 bronchus respiratory epithelial cells Medium Enhanced P15529 4179 +ENSG00000117335 CD46 lung macrophages Low Enhanced P15529 4179 +ENSG00000117335 CD46 lung pneumocytes Medium Enhanced P15529 4179 +ENSG00000117411 B4GALT2 bronchus respiratory epithelial cells Low Enhanced O60909 8704 +ENSG00000117411 B4GALT2 lung macrophages Low Enhanced O60909 8704 +ENSG00000117475 BLZF1 bronchus respiratory epithelial cells Medium Supported Q9H2G9 8548 +ENSG00000117475 BLZF1 lung macrophages Medium Supported Q9H2G9 8548 +ENSG00000117475 BLZF1 lung pneumocytes Medium Supported Q9H2G9 8548 +ENSG00000117477 CCDC181 bronchus respiratory epithelial cells High Enhanced Q5TID7 57821 +ENSG00000117505 DR1 bronchus respiratory epithelial cells Medium Enhanced Q01658 1810 +ENSG00000117505 DR1 lung macrophages Medium Enhanced Q01658 1810 +ENSG00000117505 DR1 lung pneumocytes Medium Enhanced Q01658 1810 +ENSG00000117519 CNN3 bronchus respiratory epithelial cells Medium Enhanced Q15417 1266 +ENSG00000117519 CNN3 lung macrophages Low Enhanced Q15417 1266 +ENSG00000117519 CNN3 lung pneumocytes Medium Enhanced Q15417 1266 +ENSG00000117528 ABCD3 bronchus respiratory epithelial cells High Enhanced P28288 5825 +ENSG00000117528 ABCD3 lung macrophages Medium Enhanced P28288 5825 +ENSG00000117528 ABCD3 lung pneumocytes High Enhanced P28288 5825 +ENSG00000117592 PRDX6 bronchus respiratory epithelial cells High Supported P30041 9588 +ENSG00000117592 PRDX6 lung macrophages Medium Supported P30041 9588 +ENSG00000117592 PRDX6 lung pneumocytes High Supported P30041 9588 +ENSG00000117593 DARS2 bronchus respiratory epithelial cells Medium Enhanced Q6PI48 55157 +ENSG00000117593 DARS2 lung macrophages Medium Enhanced Q6PI48 55157 +ENSG00000117593 DARS2 lung pneumocytes Low Enhanced Q6PI48 55157 +ENSG00000117595 IRF6 lung macrophages Medium Enhanced O14896 3664 +ENSG00000117595 IRF6 lung pneumocytes Medium Enhanced O14896 3664 +ENSG00000117601 SERPINC1 bronchus respiratory epithelial cells Medium Supported P01008 462 +ENSG00000117601 SERPINC1 lung macrophages Medium Supported P01008 462 +ENSG00000117601 SERPINC1 lung pneumocytes Low Supported P01008 462 +ENSG00000117602 RCAN3 lung pneumocytes Medium Enhanced Q9UKA8 11123 +ENSG00000117625 RCOR3 bronchus respiratory epithelial cells High Enhanced Q9P2K3 55758 +ENSG00000117625 RCOR3 lung macrophages Medium Enhanced Q9P2K3 55758 +ENSG00000117625 RCOR3 lung pneumocytes Low Enhanced Q9P2K3 55758 +ENSG00000117676 RPS6KA1 bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000117676 RPS6KA1 lung macrophages Medium Enhanced NA NA +ENSG00000117676 RPS6KA1 lung pneumocytes Low Enhanced NA NA +ENSG00000117697 NSL1 bronchus respiratory epithelial cells Medium Enhanced Q96IY1 25936 +ENSG00000117697 NSL1 lung macrophages Low Enhanced Q96IY1 25936 +ENSG00000117697 NSL1 lung pneumocytes Medium Enhanced Q96IY1 25936 +ENSG00000117713 ARID1A bronchus respiratory epithelial cells High Supported O14497 8289 +ENSG00000117713 ARID1A lung macrophages Medium Supported O14497 8289 +ENSG00000117713 ARID1A lung pneumocytes Medium Supported O14497 8289 +ENSG00000117748 RPA2 bronchus respiratory epithelial cells High Supported P15927 6118 +ENSG00000117748 RPA2 lung macrophages Medium Supported P15927 6118 +ENSG00000117748 RPA2 lung pneumocytes High Supported P15927 6118 +ENSG00000117751 PPP1R8 bronchus respiratory epithelial cells High Enhanced Q12972 5511 +ENSG00000117751 PPP1R8 lung macrophages High Enhanced Q12972 5511 +ENSG00000117751 PPP1R8 lung pneumocytes High Enhanced Q12972 5511 +ENSG00000117791 MARC2 bronchus respiratory epithelial cells Low Enhanced Q969Z3 54996 +ENSG00000117859 OSBPL9 bronchus respiratory epithelial cells Low Supported Q96SU4 114883 +ENSG00000117859 OSBPL9 lung macrophages Low Supported Q96SU4 114883 +ENSG00000117877 CD3EAP bronchus respiratory epithelial cells Medium Supported O15446 10849 +ENSG00000117877 CD3EAP lung macrophages Low Supported O15446 10849 +ENSG00000117877 CD3EAP lung pneumocytes Low Supported O15446 10849 +ENSG00000117983 MUC5B bronchus respiratory epithelial cells High Enhanced Q9HC84 727897 +ENSG00000117984 CTSD bronchus respiratory epithelial cells Low Enhanced P07339 1509 +ENSG00000117984 CTSD lung macrophages High Enhanced P07339 1509 +ENSG00000118007 STAG1 bronchus respiratory epithelial cells High Supported Q8WVM7 10274 +ENSG00000118007 STAG1 lung macrophages Medium Supported Q8WVM7 10274 +ENSG00000118007 STAG1 lung pneumocytes Medium Supported Q8WVM7 10274 +ENSG00000118058 KMT2A bronchus respiratory epithelial cells Medium Enhanced Q03164 4297 +ENSG00000118058 KMT2A lung macrophages Low Enhanced Q03164 4297 +ENSG00000118058 KMT2A lung pneumocytes Medium Enhanced Q03164 4297 +ENSG00000118200 CAMSAP2 bronchus respiratory epithelial cells Medium Enhanced Q08AD1 23271 +ENSG00000118200 CAMSAP2 lung macrophages Medium Enhanced Q08AD1 23271 +ENSG00000118200 CAMSAP2 lung pneumocytes Medium Enhanced Q08AD1 23271 +ENSG00000118257 NRP2 bronchus respiratory epithelial cells Low Enhanced O60462 8828 +ENSG00000118260 CREB1 bronchus respiratory epithelial cells High Supported P16220 1385 +ENSG00000118260 CREB1 lung macrophages High Supported P16220 1385 +ENSG00000118260 CREB1 lung pneumocytes High Supported P16220 1385 +ENSG00000118307 CASC1 bronchus respiratory epithelial cells Medium Enhanced Q6TDU7 55259 +ENSG00000118308 LRMP lung macrophages Medium Enhanced Q12912 4033 +ENSG00000118407 FILIP1 bronchus respiratory epithelial cells Low Enhanced Q7Z7B0 27145 +ENSG00000118407 FILIP1 lung macrophages Low Enhanced Q7Z7B0 27145 +ENSG00000118418 HMGN3 bronchus respiratory epithelial cells High Enhanced Q15651 9324 +ENSG00000118418 HMGN3 lung macrophages Medium Enhanced Q15651 9324 +ENSG00000118418 HMGN3 lung pneumocytes Medium Enhanced Q15651 9324 +ENSG00000118492 ADGB bronchus respiratory epithelial cells Medium Enhanced Q8N7X0 79747 +ENSG00000118640 VAMP8 bronchus respiratory epithelial cells High Enhanced Q9BV40 8673 +ENSG00000118640 VAMP8 lung macrophages High Enhanced Q9BV40 8673 +ENSG00000118640 VAMP8 lung pneumocytes Low Enhanced Q9BV40 8673 +ENSG00000118689 FOXO3 bronchus respiratory epithelial cells Medium Supported O43524 2309 +ENSG00000118689 FOXO3 lung pneumocytes Medium Supported O43524 2309 +ENSG00000118690 ARMC2 bronchus respiratory epithelial cells Low Enhanced Q8NEN0 84071 +ENSG00000118705 RPN2 bronchus respiratory epithelial cells Medium Enhanced P04844 6185 +ENSG00000118705 RPN2 lung macrophages Medium Enhanced P04844 6185 +ENSG00000118705 RPN2 lung pneumocytes Low Enhanced P04844 6185 +ENSG00000118777 ABCG2 lung macrophages Low Enhanced Q9UNQ0 9429 +ENSG00000118785 SPP1 bronchus respiratory epithelial cells Medium Enhanced P10451 6696 +ENSG00000118785 SPP1 lung macrophages Low Enhanced P10451 6696 +ENSG00000118898 PPL bronchus respiratory epithelial cells Medium Enhanced O60437 5493 +ENSG00000118898 PPL lung pneumocytes Low Enhanced O60437 5493 +ENSG00000118900 UBN1 bronchus respiratory epithelial cells Medium Enhanced Q9NPG3 29855 +ENSG00000118900 UBN1 lung macrophages Low Enhanced Q9NPG3 29855 +ENSG00000119139 TJP2 bronchus respiratory epithelial cells Medium Supported Q9UDY2 9414 +ENSG00000119139 TJP2 lung macrophages Low Supported Q9UDY2 9414 +ENSG00000119139 TJP2 lung pneumocytes Low Supported Q9UDY2 9414 +ENSG00000119318 RAD23B bronchus respiratory epithelial cells High Enhanced P54727 5887 +ENSG00000119318 RAD23B lung macrophages Medium Enhanced P54727 5887 +ENSG00000119318 RAD23B lung pneumocytes Medium Enhanced P54727 5887 +ENSG00000119335 SET bronchus respiratory epithelial cells High Supported Q01105 6418 +ENSG00000119335 SET lung macrophages Medium Supported Q01105 6418 +ENSG00000119335 SET lung pneumocytes Medium Supported Q01105 6418 +ENSG00000119392 GLE1 bronchus respiratory epithelial cells Medium Supported Q53GS7 2733 +ENSG00000119392 GLE1 lung macrophages Medium Supported Q53GS7 2733 +ENSG00000119392 GLE1 lung pneumocytes Medium Supported Q53GS7 2733 +ENSG00000119421 NDUFA8 bronchus respiratory epithelial cells Medium Enhanced P51970 4702 +ENSG00000119421 NDUFA8 lung macrophages Medium Enhanced P51970 4702 +ENSG00000119421 NDUFA8 lung pneumocytes Medium Enhanced P51970 4702 +ENSG00000119431 HDHD3 bronchus respiratory epithelial cells Medium Enhanced Q9BSH5 81932 +ENSG00000119431 HDHD3 lung macrophages Low Enhanced Q9BSH5 81932 +ENSG00000119471 HSDL2 bronchus respiratory epithelial cells Medium Enhanced Q6YN16 84263 +ENSG00000119471 HSDL2 lung macrophages High Enhanced Q6YN16 84263 +ENSG00000119471 HSDL2 lung pneumocytes Medium Enhanced Q6YN16 84263 +ENSG00000119487 MAPKAP1 bronchus respiratory epithelial cells Medium Enhanced Q9BPZ7 79109 +ENSG00000119487 MAPKAP1 lung macrophages High Enhanced Q9BPZ7 79109 +ENSG00000119514 GALNT12 bronchus respiratory epithelial cells High Enhanced Q8IXK2 79695 +ENSG00000119514 GALNT12 lung macrophages Medium Enhanced Q8IXK2 79695 +ENSG00000119535 CSF3R lung macrophages Low Enhanced Q99062 1441 +ENSG00000119655 NPC2 bronchus respiratory epithelial cells Low Enhanced P61916 10577 +ENSG00000119655 NPC2 lung macrophages High Enhanced P61916 10577 +ENSG00000119655 NPC2 lung pneumocytes High Enhanced P61916 10577 +ENSG00000119673 ACOT2 bronchus respiratory epithelial cells High Enhanced P49753 10965 +ENSG00000119673 ACOT2 lung pneumocytes Medium Enhanced P49753 10965 +ENSG00000119686 FLVCR2 bronchus respiratory epithelial cells Low Enhanced Q9UPI3 55640 +ENSG00000119686 FLVCR2 lung macrophages Medium Enhanced Q9UPI3 55640 +ENSG00000119689 DLST bronchus respiratory epithelial cells Medium Supported P36957 1743 +ENSG00000119689 DLST lung macrophages Medium Supported P36957 1743 +ENSG00000119707 RBM25 lung macrophages High Supported P49756 58517 +ENSG00000119707 RBM25 lung pneumocytes Medium Supported P49756 58517 +ENSG00000119711 ALDH6A1 bronchus respiratory epithelial cells Low Enhanced Q02252 4329 +ENSG00000119718 EIF2B2 bronchus respiratory epithelial cells High Enhanced P49770 8892 +ENSG00000119718 EIF2B2 lung macrophages Medium Enhanced P49770 8892 +ENSG00000119718 EIF2B2 lung pneumocytes Medium Enhanced P49770 8892 +ENSG00000119820 YIPF4 bronchus respiratory epithelial cells High Supported Q9BSR8 84272 +ENSG00000119820 YIPF4 lung macrophages Medium Supported Q9BSR8 84272 +ENSG00000119820 YIPF4 lung pneumocytes Low Supported Q9BSR8 84272 +ENSG00000119888 EPCAM bronchus respiratory epithelial cells Low Enhanced P16422 4072 +ENSG00000119965 C10orf88 bronchus respiratory epithelial cells Low Enhanced Q9H8K7 80007 +ENSG00000119969 HELLS bronchus respiratory epithelial cells Low Enhanced Q9NRZ9 3070 +ENSG00000119969 HELLS lung macrophages Low Enhanced Q9NRZ9 3070 +ENSG00000120053 GOT1 bronchus respiratory epithelial cells Low Enhanced P17174 2805 +ENSG00000120217 CD274 lung macrophages High Enhanced Q9NZQ7 29126 +ENSG00000120253 NUP43 bronchus respiratory epithelial cells High Enhanced Q8NFH3 348995 +ENSG00000120253 NUP43 lung macrophages High Enhanced Q8NFH3 348995 +ENSG00000120253 NUP43 lung pneumocytes Medium Enhanced Q8NFH3 348995 +ENSG00000120262 CCDC170 bronchus respiratory epithelial cells High Enhanced Q8IYT3 80129 +ENSG00000120289 MAGEB4 bronchus respiratory epithelial cells Low Enhanced O15481 4115 +ENSG00000120306 CYSTM1 bronchus respiratory epithelial cells Low Enhanced Q9H1C7 84418 +ENSG00000120437 ACAT2 bronchus respiratory epithelial cells Medium Enhanced Q9BWD1 39 +ENSG00000120437 ACAT2 lung macrophages Medium Enhanced Q9BWD1 39 +ENSG00000120437 ACAT2 lung pneumocytes Medium Enhanced Q9BWD1 39 +ENSG00000120457 KCNJ5 bronchus respiratory epithelial cells Low Enhanced P48544 3762 +ENSG00000120457 KCNJ5 lung macrophages Medium Enhanced P48544 3762 +ENSG00000120457 KCNJ5 lung pneumocytes Low Enhanced P48544 3762 +ENSG00000120658 ENOX1 bronchus respiratory epithelial cells Medium Supported Q8TC92 55068 +ENSG00000120658 ENOX1 lung macrophages Medium Supported Q8TC92 55068 +ENSG00000120694 HSPH1 bronchus respiratory epithelial cells High Enhanced Q92598 10808 +ENSG00000120694 HSPH1 lung macrophages High Enhanced Q92598 10808 +ENSG00000120708 TGFBI lung macrophages Medium Enhanced Q15582 7045 +ENSG00000120725 SIL1 bronchus respiratory epithelial cells Medium Enhanced Q9H173 64374 +ENSG00000120725 SIL1 lung macrophages Medium Enhanced Q9H173 64374 +ENSG00000120725 SIL1 lung pneumocytes Medium Enhanced Q9H173 64374 +ENSG00000120733 KDM3B bronchus respiratory epithelial cells High Supported Q7LBC6 51780 +ENSG00000120733 KDM3B lung macrophages Medium Supported Q7LBC6 51780 +ENSG00000120733 KDM3B lung pneumocytes High Supported Q7LBC6 51780 +ENSG00000120738 EGR1 bronchus respiratory epithelial cells Medium Enhanced P18146 1958 +ENSG00000120738 EGR1 lung pneumocytes Low Enhanced P18146 1958 +ENSG00000120756 PLS1 lung macrophages Medium Enhanced Q14651 5357 +ENSG00000120798 NR2C1 bronchus respiratory epithelial cells Medium Enhanced P13056 7181 +ENSG00000120798 NR2C1 lung pneumocytes Medium Enhanced P13056 7181 +ENSG00000120802 TMPO bronchus respiratory epithelial cells High Enhanced P42166 7112 +ENSG00000120802 TMPO lung macrophages Low Enhanced P42166 7112 +ENSG00000120802 TMPO lung pneumocytes High Enhanced P42166 7112 +ENSG00000120837 NFYB bronchus respiratory epithelial cells High Supported P25208 4801 +ENSG00000120837 NFYB lung macrophages High Supported P25208 4801 +ENSG00000120837 NFYB lung pneumocytes High Supported P25208 4801 +ENSG00000120868 APAF1 bronchus respiratory epithelial cells Low Enhanced O14727 317 +ENSG00000120948 TARDBP bronchus respiratory epithelial cells High Supported Q13148 23435 +ENSG00000120948 TARDBP lung macrophages High Supported Q13148 23435 +ENSG00000120948 TARDBP lung pneumocytes High Supported Q13148 23435 +ENSG00000120992 LYPLA1 bronchus respiratory epithelial cells Medium Enhanced O75608 10434 +ENSG00000120992 LYPLA1 lung macrophages Medium Enhanced O75608 10434 +ENSG00000121022 COPS5 bronchus respiratory epithelial cells High Supported Q92905 10987 +ENSG00000121022 COPS5 lung macrophages High Supported Q92905 10987 +ENSG00000121022 COPS5 lung pneumocytes High Supported Q92905 10987 +ENSG00000121057 AKAP1 bronchus respiratory epithelial cells Medium Supported Q92667 8165 +ENSG00000121057 AKAP1 lung macrophages Medium Supported Q92667 8165 +ENSG00000121057 AKAP1 lung pneumocytes Medium Supported Q92667 8165 +ENSG00000121058 COIL bronchus respiratory epithelial cells Medium Enhanced P38432 8161 +ENSG00000121211 MND1 lung macrophages Medium Enhanced Q9BWT6 84057 +ENSG00000121390 PSPC1 lung macrophages Low Supported Q8WXF1 55269 +ENSG00000121390 PSPC1 lung pneumocytes High Supported Q8WXF1 55269 +ENSG00000121413 ZSCAN18 bronchus respiratory epithelial cells High Supported Q8TBC5 65982 +ENSG00000121413 ZSCAN18 lung macrophages High Supported Q8TBC5 65982 +ENSG00000121552 CSTA bronchus respiratory epithelial cells Low Enhanced P01040 1475 +ENSG00000121552 CSTA lung macrophages Low Enhanced P01040 1475 +ENSG00000121671 CRY2 bronchus respiratory epithelial cells High Supported Q49AN0 1408 +ENSG00000121671 CRY2 lung macrophages High Supported Q49AN0 1408 +ENSG00000121671 CRY2 lung pneumocytes High Supported Q49AN0 1408 +ENSG00000121691 CAT lung macrophages Low Enhanced P04040 847 +ENSG00000121749 TBC1D15 bronchus respiratory epithelial cells Medium Supported Q8TC07 64786 +ENSG00000121749 TBC1D15 lung macrophages Medium Supported Q8TC07 64786 +ENSG00000121749 TBC1D15 lung pneumocytes Medium Supported Q8TC07 64786 +ENSG00000121774 KHDRBS1 bronchus respiratory epithelial cells High Enhanced Q07666 10657 +ENSG00000121774 KHDRBS1 lung macrophages High Enhanced Q07666 10657 +ENSG00000121774 KHDRBS1 lung pneumocytes High Enhanced Q07666 10657 +ENSG00000121892 PDS5A bronchus respiratory epithelial cells High Enhanced Q29RF7 23244 +ENSG00000121892 PDS5A lung macrophages Medium Enhanced Q29RF7 23244 +ENSG00000121892 PDS5A lung pneumocytes Medium Enhanced Q29RF7 23244 +ENSG00000121940 CLCC1 bronchus respiratory epithelial cells High Enhanced Q96S66 23155 +ENSG00000121940 CLCC1 lung macrophages High Enhanced Q96S66 23155 +ENSG00000121940 CLCC1 lung pneumocytes Medium Enhanced Q96S66 23155 +ENSG00000122034 GTF3A bronchus respiratory epithelial cells High Supported Q92664 2971 +ENSG00000122034 GTF3A lung macrophages Medium Supported Q92664 2971 +ENSG00000122034 GTF3A lung pneumocytes Low Supported Q92664 2971 +ENSG00000122035 RASL11A bronchus respiratory epithelial cells Medium Supported Q6T310 387496 +ENSG00000122035 RASL11A lung macrophages Low Supported Q6T310 387496 +ENSG00000122035 RASL11A lung pneumocytes High Supported Q6T310 387496 +ENSG00000122122 SASH3 bronchus respiratory epithelial cells Low Enhanced O75995 54440 +ENSG00000122122 SASH3 lung macrophages Low Enhanced O75995 54440 +ENSG00000122218 COPA bronchus respiratory epithelial cells Medium Supported P53621 1314 +ENSG00000122218 COPA lung macrophages Medium Supported P53621 1314 +ENSG00000122218 COPA lung pneumocytes Low Supported P53621 1314 +ENSG00000122335 SERAC1 bronchus respiratory epithelial cells High Enhanced Q96JX3 84947 +ENSG00000122335 SERAC1 lung macrophages High Enhanced Q96JX3 84947 +ENSG00000122335 SERAC1 lung pneumocytes Medium Enhanced Q96JX3 84947 +ENSG00000122359 ANXA11 bronchus respiratory epithelial cells High Supported P50995 311 +ENSG00000122359 ANXA11 lung macrophages Medium Supported P50995 311 +ENSG00000122359 ANXA11 lung pneumocytes Low Supported P50995 311 +ENSG00000122515 ZMIZ2 bronchus respiratory epithelial cells Medium Supported Q8NF64 83637 +ENSG00000122515 ZMIZ2 lung macrophages Low Supported Q8NF64 83637 +ENSG00000122515 ZMIZ2 lung pneumocytes Medium Supported Q8NF64 83637 +ENSG00000122545 SEPT7 bronchus respiratory epithelial cells Low Enhanced Q16181 989 +ENSG00000122545 SEPT7 lung macrophages Low Enhanced Q16181 989 +ENSG00000122565 CBX3 bronchus respiratory epithelial cells Medium Enhanced Q13185 11335 +ENSG00000122565 CBX3 lung macrophages Medium Enhanced Q13185 11335 +ENSG00000122565 CBX3 lung pneumocytes Medium Enhanced Q13185 11335 +ENSG00000122566 HNRNPA2B1 bronchus respiratory epithelial cells High Supported P22626 3181 +ENSG00000122566 HNRNPA2B1 lung macrophages High Supported P22626 3181 +ENSG00000122566 HNRNPA2B1 lung pneumocytes High Supported P22626 3181 +ENSG00000122692 SMU1 bronchus respiratory epithelial cells Medium Supported Q2TAY7 55234 +ENSG00000122692 SMU1 lung macrophages Medium Supported Q2TAY7 55234 +ENSG00000122705 CLTA bronchus respiratory epithelial cells Medium Enhanced P09496 1211 +ENSG00000122705 CLTA lung pneumocytes Low Enhanced P09496 1211 +ENSG00000122707 RECK lung pneumocytes Medium Supported O95980 8434 +ENSG00000122729 ACO1 lung macrophages Medium Enhanced P21399 48 +ENSG00000122735 DNAI1 bronchus respiratory epithelial cells Medium Enhanced Q9UI46 27019 +ENSG00000122786 CALD1 lung macrophages Low Enhanced Q05682 800 +ENSG00000122786 CALD1 lung pneumocytes Low Enhanced Q05682 800 +ENSG00000122852 SFTPA1 lung pneumocytes High Supported Q8IWL2 653509 +ENSG00000122862 SRGN lung macrophages Low Enhanced P10124 5552 +ENSG00000122863 CHST3 bronchus respiratory epithelial cells Low Enhanced Q7LGC8 9469 +ENSG00000122863 CHST3 lung macrophages Low Enhanced Q7LGC8 9469 +ENSG00000122870 BICC1 bronchus respiratory epithelial cells High Enhanced Q9H694 80114 +ENSG00000122870 BICC1 lung macrophages High Enhanced Q9H694 80114 +ENSG00000122870 BICC1 lung pneumocytes Medium Enhanced Q9H694 80114 +ENSG00000122884 P4HA1 bronchus respiratory epithelial cells High Enhanced P13674 5033 +ENSG00000122884 P4HA1 lung macrophages High Enhanced P13674 5033 +ENSG00000122884 P4HA1 lung pneumocytes Medium Enhanced P13674 5033 +ENSG00000122952 ZWINT bronchus respiratory epithelial cells Medium Enhanced O95229 11130 +ENSG00000122952 ZWINT lung macrophages Medium Enhanced O95229 11130 +ENSG00000122958 VPS26A bronchus respiratory epithelial cells Medium Enhanced O75436 9559 +ENSG00000122958 VPS26A lung macrophages Medium Enhanced O75436 9559 +ENSG00000122958 VPS26A lung pneumocytes Medium Enhanced O75436 9559 +ENSG00000122965 RBM19 bronchus respiratory epithelial cells Medium Supported Q9Y4C8 9904 +ENSG00000122965 RBM19 lung macrophages Low Supported Q9Y4C8 9904 +ENSG00000122965 RBM19 lung pneumocytes Medium Supported Q9Y4C8 9904 +ENSG00000122970 IFT81 bronchus respiratory epithelial cells Medium Enhanced Q8WYA0 28981 +ENSG00000122970 IFT81 lung macrophages Medium Enhanced Q8WYA0 28981 +ENSG00000122971 ACADS bronchus respiratory epithelial cells Medium Enhanced P16219 35 +ENSG00000122971 ACADS lung macrophages Medium Enhanced P16219 35 +ENSG00000122971 ACADS lung pneumocytes Medium Enhanced P16219 35 +ENSG00000122986 HVCN1 lung macrophages Low Enhanced Q96D96 84329 +ENSG00000123130 ACOT9 bronchus respiratory epithelial cells High Supported Q9Y305 23597 +ENSG00000123130 ACOT9 lung macrophages High Supported Q9Y305 23597 +ENSG00000123130 ACOT9 lung pneumocytes Medium Supported Q9Y305 23597 +ENSG00000123131 PRDX4 bronchus respiratory epithelial cells Medium Enhanced Q13162 10549 +ENSG00000123131 PRDX4 lung macrophages Medium Enhanced Q13162 10549 +ENSG00000123131 PRDX4 lung pneumocytes Medium Enhanced Q13162 10549 +ENSG00000123146 ADGRE5 lung macrophages Medium Enhanced P48960 976 +ENSG00000123191 ATP7B bronchus respiratory epithelial cells Medium Supported P35670 540 +ENSG00000123191 ATP7B lung macrophages Low Supported P35670 540 +ENSG00000123240 OPTN bronchus respiratory epithelial cells High Supported Q96CV9 10133 +ENSG00000123240 OPTN lung macrophages High Supported Q96CV9 10133 +ENSG00000123240 OPTN lung pneumocytes High Supported Q96CV9 10133 +ENSG00000123268 ATF1 bronchus respiratory epithelial cells Medium Enhanced P18846 466 +ENSG00000123268 ATF1 lung macrophages Low Enhanced P18846 466 +ENSG00000123268 ATF1 lung pneumocytes Medium Enhanced P18846 466 +ENSG00000123384 LRP1 bronchus respiratory epithelial cells Low Supported Q07954 4035 +ENSG00000123384 LRP1 lung macrophages Medium Supported Q07954 4035 +ENSG00000123384 LRP1 lung pneumocytes Low Supported Q07954 4035 +ENSG00000123416 TUBA1B bronchus respiratory epithelial cells High Enhanced P68363 10376 +ENSG00000123416 TUBA1B lung macrophages High Enhanced P68363 10376 +ENSG00000123416 TUBA1B lung pneumocytes High Enhanced P68363 10376 +ENSG00000123562 MORF4L2 bronchus respiratory epithelial cells High Supported Q15014 9643 +ENSG00000123562 MORF4L2 lung macrophages Low Supported Q15014 9643 +ENSG00000123562 MORF4L2 lung pneumocytes High Supported Q15014 9643 +ENSG00000123570 RAB9B bronchus respiratory epithelial cells Low Enhanced Q9NP90 51209 +ENSG00000123570 RAB9B lung macrophages Low Enhanced Q9NP90 51209 +ENSG00000123595 RAB9A bronchus respiratory epithelial cells High Enhanced P51151 9367 +ENSG00000123595 RAB9A lung macrophages High Enhanced P51151 9367 +ENSG00000123810 B9D2 bronchus respiratory epithelial cells Medium Enhanced Q9BPU9 80776 +ENSG00000123810 B9D2 lung macrophages Low Enhanced Q9BPU9 80776 +ENSG00000123810 B9D2 lung pneumocytes Low Enhanced Q9BPU9 80776 +ENSG00000123815 COQ8B bronchus respiratory epithelial cells High Enhanced Q96D53 79934 +ENSG00000123815 COQ8B lung macrophages High Enhanced Q96D53 79934 +ENSG00000123815 COQ8B lung pneumocytes Medium Enhanced Q96D53 79934 +ENSG00000123838 C4BPA lung macrophages Medium Enhanced P04003 722 +ENSG00000123838 C4BPA lung pneumocytes Low Enhanced P04003 722 +ENSG00000123992 DNPEP bronchus respiratory epithelial cells High Enhanced Q9ULA0 23549 +ENSG00000123992 DNPEP lung macrophages Medium Enhanced Q9ULA0 23549 +ENSG00000123992 DNPEP lung pneumocytes High Enhanced Q9ULA0 23549 +ENSG00000124102 PI3 lung macrophages Low Enhanced P19957 5266 +ENSG00000124107 SLPI bronchus respiratory epithelial cells Medium Enhanced P03973 6590 +ENSG00000124126 PREX1 lung macrophages High Supported Q8TCU6 57580 +ENSG00000124145 SDC4 bronchus respiratory epithelial cells High Supported P31431 6385 +ENSG00000124145 SDC4 lung macrophages Medium Supported P31431 6385 +ENSG00000124145 SDC4 lung pneumocytes High Supported P31431 6385 +ENSG00000124151 NCOA3 bronchus respiratory epithelial cells Medium Supported Q9Y6Q9 8202 +ENSG00000124151 NCOA3 lung macrophages Medium Supported Q9Y6Q9 8202 +ENSG00000124151 NCOA3 lung pneumocytes Medium Supported Q9Y6Q9 8202 +ENSG00000124164 VAPB bronchus respiratory epithelial cells Medium Supported O95292 9217 +ENSG00000124164 VAPB lung macrophages Medium Supported O95292 9217 +ENSG00000124164 VAPB lung pneumocytes Medium Supported O95292 9217 +ENSG00000124193 SRSF6 bronchus respiratory epithelial cells High Supported Q13247 6431 +ENSG00000124193 SRSF6 lung macrophages Medium Supported Q13247 6431 +ENSG00000124193 SRSF6 lung pneumocytes High Supported Q13247 6431 +ENSG00000124198 ARFGEF2 bronchus respiratory epithelial cells Medium Supported Q9Y6D5 10564 +ENSG00000124198 ARFGEF2 lung macrophages Medium Supported Q9Y6D5 10564 +ENSG00000124198 ARFGEF2 lung pneumocytes Medium Supported Q9Y6D5 10564 +ENSG00000124212 PTGIS bronchus respiratory epithelial cells Medium Enhanced Q16647 5740 +ENSG00000124212 PTGIS lung macrophages Medium Enhanced Q16647 5740 +ENSG00000124212 PTGIS lung pneumocytes Low Enhanced Q16647 5740 +ENSG00000124216 SNAI1 bronchus respiratory epithelial cells High Supported O95863 6615 +ENSG00000124216 SNAI1 lung macrophages Medium Supported O95863 6615 +ENSG00000124216 SNAI1 lung pneumocytes High Supported O95863 6615 +ENSG00000124237 C20orf85 bronchus respiratory epithelial cells Medium Enhanced Q9H1P6 128602 +ENSG00000124256 ZBP1 bronchus respiratory epithelial cells Low Enhanced Q9H171 81030 +ENSG00000124256 ZBP1 lung macrophages Low Enhanced Q9H171 81030 +ENSG00000124275 MTRR bronchus respiratory epithelial cells Medium Supported Q9UBK8 4552 +ENSG00000124275 MTRR lung macrophages Medium Supported Q9UBK8 4552 +ENSG00000124357 NAGK lung macrophages Medium Enhanced Q9UJ70 55577 +ENSG00000124383 MPHOSPH10 lung macrophages Low Enhanced O00566 10199 +ENSG00000124383 MPHOSPH10 lung pneumocytes Low Enhanced O00566 10199 +ENSG00000124406 ATP8A1 bronchus respiratory epithelial cells Low Enhanced Q9Y2Q0 10396 +ENSG00000124406 ATP8A1 lung macrophages Medium Enhanced Q9Y2Q0 10396 +ENSG00000124422 USP22 bronchus respiratory epithelial cells High Supported Q9UPT9 23326 +ENSG00000124422 USP22 lung macrophages High Supported Q9UPT9 23326 +ENSG00000124422 USP22 lung pneumocytes High Supported Q9UPT9 23326 +ENSG00000124496 TRERF1 bronchus respiratory epithelial cells Medium Enhanced Q96PN7 55809 +ENSG00000124496 TRERF1 lung pneumocytes Low Enhanced Q96PN7 55809 +ENSG00000124535 WRNIP1 bronchus respiratory epithelial cells Medium Enhanced Q96S55 56897 +ENSG00000124535 WRNIP1 lung macrophages Low Enhanced Q96S55 56897 +ENSG00000124535 WRNIP1 lung pneumocytes Low Enhanced Q96S55 56897 +ENSG00000124562 SNRPC bronchus respiratory epithelial cells High Supported P09234 6631 +ENSG00000124562 SNRPC lung macrophages High Supported P09234 6631 +ENSG00000124562 SNRPC lung pneumocytes High Supported P09234 6631 +ENSG00000124570 SERPINB6 bronchus respiratory epithelial cells High Enhanced P35237 5269 +ENSG00000124570 SERPINB6 lung macrophages High Enhanced P35237 5269 +ENSG00000124570 SERPINB6 lung pneumocytes High Enhanced P35237 5269 +ENSG00000124571 XPO5 bronchus respiratory epithelial cells High Enhanced Q9HAV4 57510 +ENSG00000124571 XPO5 lung macrophages Low Enhanced Q9HAV4 57510 +ENSG00000124571 XPO5 lung pneumocytes Low Enhanced Q9HAV4 57510 +ENSG00000124587 PEX6 bronchus respiratory epithelial cells Medium Enhanced Q13608 5190 +ENSG00000124587 PEX6 lung macrophages Low Enhanced Q13608 5190 +ENSG00000124587 PEX6 lung pneumocytes Low Enhanced Q13608 5190 +ENSG00000124588 NQO2 bronchus respiratory epithelial cells Low Enhanced P16083 4835 +ENSG00000124588 NQO2 lung macrophages Low Enhanced P16083 4835 +ENSG00000124602 UNC5CL bronchus respiratory epithelial cells Low Enhanced Q8IV45 222643 +ENSG00000124610 HIST1H1A bronchus respiratory epithelial cells High Supported Q02539 3024 +ENSG00000124610 HIST1H1A lung macrophages Low Supported Q02539 3024 +ENSG00000124610 HIST1H1A lung pneumocytes Medium Supported Q02539 3024 +ENSG00000124635 HIST1H2BJ bronchus respiratory epithelial cells High Supported P06899 8970 +ENSG00000124635 HIST1H2BJ lung macrophages High Supported P06899 8970 +ENSG00000124635 HIST1H2BJ lung pneumocytes High Supported P06899 8970 +ENSG00000124762 CDKN1A bronchus respiratory epithelial cells High Supported P38936 1026 +ENSG00000124762 CDKN1A lung macrophages Medium Supported P38936 1026 +ENSG00000124767 GLO1 bronchus respiratory epithelial cells Medium Enhanced Q04760 2739 +ENSG00000124767 GLO1 lung macrophages Low Enhanced Q04760 2739 +ENSG00000124767 GLO1 lung pneumocytes Low Enhanced Q04760 2739 +ENSG00000124783 SSR1 bronchus respiratory epithelial cells Medium Enhanced P43307 6745 +ENSG00000124783 SSR1 lung macrophages Low Enhanced P43307 6745 +ENSG00000124784 RIOK1 bronchus respiratory epithelial cells Low Enhanced Q9BRS2 83732 +ENSG00000124789 NUP153 bronchus respiratory epithelial cells High Enhanced P49790 9972 +ENSG00000124789 NUP153 lung macrophages Medium Enhanced P49790 9972 +ENSG00000124789 NUP153 lung pneumocytes Medium Enhanced P49790 9972 +ENSG00000124795 DEK bronchus respiratory epithelial cells Medium Enhanced P35659 7913 +ENSG00000124795 DEK lung macrophages Medium Enhanced P35659 7913 +ENSG00000124795 DEK lung pneumocytes Medium Enhanced P35659 7913 +ENSG00000124813 RUNX2 bronchus respiratory epithelial cells Low Enhanced Q13950 860 +ENSG00000125166 GOT2 bronchus respiratory epithelial cells Medium Enhanced P00505 2806 +ENSG00000125166 GOT2 lung macrophages Low Enhanced P00505 2806 +ENSG00000125170 DOK4 bronchus respiratory epithelial cells Medium Supported Q8TEW6 55715 +ENSG00000125170 DOK4 lung macrophages Low Supported Q8TEW6 55715 +ENSG00000125246 CLYBL bronchus respiratory epithelial cells High Enhanced Q8N0X4 171425 +ENSG00000125246 CLYBL lung macrophages High Enhanced Q8N0X4 171425 +ENSG00000125246 CLYBL lung pneumocytes High Enhanced Q8N0X4 171425 +ENSG00000125266 EFNB2 bronchus respiratory epithelial cells Medium Supported P52799 1948 +ENSG00000125266 EFNB2 lung macrophages Medium Supported P52799 1948 +ENSG00000125266 EFNB2 lung pneumocytes Medium Supported P52799 1948 +ENSG00000125304 TM9SF2 bronchus respiratory epithelial cells Low Supported Q99805 9375 +ENSG00000125304 TM9SF2 lung macrophages High Supported Q99805 9375 +ENSG00000125347 IRF1 bronchus respiratory epithelial cells Medium Supported P10914 3659 +ENSG00000125347 IRF1 lung macrophages Medium Supported P10914 3659 +ENSG00000125354 SEPT6 bronchus respiratory epithelial cells High Supported Q14141 23157 +ENSG00000125354 SEPT6 lung macrophages Medium Supported Q14141 23157 +ENSG00000125356 NDUFA1 bronchus respiratory epithelial cells Medium Enhanced O15239 4694 +ENSG00000125378 BMP4 bronchus respiratory epithelial cells Medium Enhanced P12644 652 +ENSG00000125378 BMP4 lung macrophages High Enhanced P12644 652 +ENSG00000125398 SOX9 bronchus respiratory epithelial cells Medium Enhanced P48436 6662 +ENSG00000125414 MYH2 lung macrophages Low Enhanced Q9UKX2 4620 +ENSG00000125445 MRPS7 bronchus respiratory epithelial cells High Supported Q9Y2R9 51081 +ENSG00000125445 MRPS7 lung macrophages Medium Supported Q9Y2R9 51081 +ENSG00000125445 MRPS7 lung pneumocytes Low Supported Q9Y2R9 51081 +ENSG00000125450 NUP85 bronchus respiratory epithelial cells Medium Enhanced Q9BW27 79902 +ENSG00000125450 NUP85 lung macrophages Low Enhanced Q9BW27 79902 +ENSG00000125450 NUP85 lung pneumocytes Low Enhanced Q9BW27 79902 +ENSG00000125482 TTF1 bronchus respiratory epithelial cells Medium Supported Q15361 7270 +ENSG00000125482 TTF1 lung pneumocytes Medium Supported Q15361 7270 +ENSG00000125637 PSD4 bronchus respiratory epithelial cells Medium Enhanced Q8NDX1 23550 +ENSG00000125637 PSD4 lung macrophages Low Enhanced Q8NDX1 23550 +ENSG00000125651 GTF2F1 bronchus respiratory epithelial cells High Supported P35269 2962 +ENSG00000125651 GTF2F1 lung macrophages High Supported P35269 2962 +ENSG00000125651 GTF2F1 lung pneumocytes High Supported P35269 2962 +ENSG00000125656 CLPP bronchus respiratory epithelial cells Medium Supported Q16740 8192 +ENSG00000125656 CLPP lung macrophages High Supported Q16740 8192 +ENSG00000125676 THOC2 bronchus respiratory epithelial cells High Supported Q8NI27 57187 +ENSG00000125676 THOC2 lung macrophages High Supported Q8NI27 57187 +ENSG00000125676 THOC2 lung pneumocytes High Supported Q8NI27 57187 +ENSG00000125743 SNRPD2 bronchus respiratory epithelial cells High Supported P62316 6633 +ENSG00000125743 SNRPD2 lung macrophages Medium Supported P62316 6633 +ENSG00000125743 SNRPD2 lung pneumocytes High Supported P62316 6633 +ENSG00000125753 VASP bronchus respiratory epithelial cells High Enhanced P50552 7408 +ENSG00000125753 VASP lung macrophages High Enhanced P50552 7408 +ENSG00000125753 VASP lung pneumocytes Medium Enhanced P50552 7408 +ENSG00000125775 SDCBP2 bronchus respiratory epithelial cells Medium Enhanced Q9H190 27111 +ENSG00000125798 FOXA2 bronchus respiratory epithelial cells Medium Enhanced Q9Y261 3170 +ENSG00000125798 FOXA2 lung macrophages Low Enhanced Q9Y261 3170 +ENSG00000125798 FOXA2 lung pneumocytes Medium Enhanced Q9Y261 3170 +ENSG00000125810 CD93 lung macrophages Low Enhanced Q9NPY3 22918 +ENSG00000125827 TMX4 bronchus respiratory epithelial cells High Enhanced Q9H1E5 56255 +ENSG00000125827 TMX4 lung macrophages Low Enhanced Q9H1E5 56255 +ENSG00000125827 TMX4 lung pneumocytes Medium Enhanced Q9H1E5 56255 +ENSG00000125844 RRBP1 bronchus respiratory epithelial cells High Enhanced Q9P2E9 6238 +ENSG00000125844 RRBP1 lung macrophages High Enhanced Q9P2E9 6238 +ENSG00000125844 RRBP1 lung pneumocytes High Enhanced Q9P2E9 6238 +ENSG00000125846 ZNF133 bronchus respiratory epithelial cells Medium Enhanced P52736 7692 +ENSG00000125846 ZNF133 lung macrophages Medium Enhanced P52736 7692 +ENSG00000125846 ZNF133 lung pneumocytes Medium Enhanced P52736 7692 +ENSG00000125848 FLRT3 bronchus respiratory epithelial cells Medium Enhanced Q9NZU0 23767 +ENSG00000125848 FLRT3 lung macrophages High Enhanced Q9NZU0 23767 +ENSG00000125863 MKKS bronchus respiratory epithelial cells Medium Enhanced Q9NPJ1 8195 +ENSG00000125863 MKKS lung macrophages High Enhanced Q9NPJ1 8195 +ENSG00000125870 SNRPB2 bronchus respiratory epithelial cells High Supported P08579 6629 +ENSG00000125870 SNRPB2 lung macrophages Medium Supported P08579 6629 +ENSG00000125870 SNRPB2 lung pneumocytes Medium Supported P08579 6629 +ENSG00000125901 MRPS26 bronchus respiratory epithelial cells High Supported Q9BYN8 64949 +ENSG00000125901 MRPS26 lung macrophages Medium Supported Q9BYN8 64949 +ENSG00000125901 MRPS26 lung pneumocytes Low Supported Q9BYN8 64949 +ENSG00000125931 CITED1 lung macrophages Low Enhanced Q99966 4435 +ENSG00000125944 HNRNPR bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000125944 HNRNPR lung macrophages Medium Enhanced NA NA +ENSG00000125944 HNRNPR lung pneumocytes Medium Enhanced NA NA +ENSG00000125945 ZNF436 bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000125945 ZNF436 lung macrophages Medium Enhanced NA NA +ENSG00000125952 MAX bronchus respiratory epithelial cells Low Enhanced P61244 4149 +ENSG00000125952 MAX lung macrophages High Enhanced P61244 4149 +ENSG00000125952 MAX lung pneumocytes High Enhanced P61244 4149 +ENSG00000125967 NECAB3 bronchus respiratory epithelial cells High Supported Q96P71 63941 +ENSG00000125967 NECAB3 lung macrophages High Supported Q96P71 63941 +ENSG00000125967 NECAB3 lung pneumocytes Medium Supported Q96P71 63941 +ENSG00000125970 RALY bronchus respiratory epithelial cells High Enhanced Q9UKM9 22913 +ENSG00000125970 RALY lung macrophages High Enhanced Q9UKM9 22913 +ENSG00000125970 RALY lung pneumocytes High Enhanced Q9UKM9 22913 +ENSG00000125999 BPIFB1 bronchus respiratory epithelial cells High Supported Q8TDL5 92747 +ENSG00000126016 AMOT lung macrophages Medium Enhanced Q4VCS5 154796 +ENSG00000126062 TMEM115 bronchus respiratory epithelial cells Medium Supported Q12893 11070 +ENSG00000126062 TMEM115 lung macrophages Medium Supported Q12893 11070 +ENSG00000126062 TMEM115 lung pneumocytes Medium Supported Q12893 11070 +ENSG00000126231 PROZ bronchus respiratory epithelial cells Low Enhanced P22891 8858 +ENSG00000126231 PROZ lung macrophages Low Enhanced P22891 8858 +ENSG00000126254 RBM42 bronchus respiratory epithelial cells Medium Supported Q9BTD8 79171 +ENSG00000126254 RBM42 lung macrophages Medium Supported Q9BTD8 79171 +ENSG00000126254 RBM42 lung pneumocytes Medium Supported Q9BTD8 79171 +ENSG00000126261 UBA2 bronchus respiratory epithelial cells High Supported Q9UBT2 10054 +ENSG00000126261 UBA2 lung macrophages Low Supported Q9UBT2 10054 +ENSG00000126261 UBA2 lung pneumocytes High Supported Q9UBT2 10054 +ENSG00000126264 HCST lung macrophages Low Enhanced Q9UBK5 10870 +ENSG00000126267 COX6B1 bronchus respiratory epithelial cells High Enhanced P14854 1340 +ENSG00000126267 COX6B1 lung macrophages Medium Enhanced P14854 1340 +ENSG00000126267 COX6B1 lung pneumocytes Medium Enhanced P14854 1340 +ENSG00000126353 CCR7 lung pneumocytes High Enhanced P32248 1236 +ENSG00000126432 PRDX5 bronchus respiratory epithelial cells High Enhanced P30044 25824 +ENSG00000126432 PRDX5 lung macrophages Medium Enhanced P30044 25824 +ENSG00000126432 PRDX5 lung pneumocytes Medium Enhanced P30044 25824 +ENSG00000126457 PRMT1 bronchus respiratory epithelial cells Low Enhanced Q99873 3276 +ENSG00000126457 PRMT1 lung macrophages Low Enhanced Q99873 3276 +ENSG00000126581 BECN1 bronchus respiratory epithelial cells Low Enhanced Q14457 8678 +ENSG00000126581 BECN1 lung macrophages Medium Enhanced Q14457 8678 +ENSG00000126581 BECN1 lung pneumocytes Low Enhanced Q14457 8678 +ENSG00000126602 TRAP1 bronchus respiratory epithelial cells High Enhanced Q12931 10131 +ENSG00000126602 TRAP1 lung macrophages High Enhanced Q12931 10131 +ENSG00000126602 TRAP1 lung pneumocytes High Enhanced Q12931 10131 +ENSG00000126653 NSRP1 bronchus respiratory epithelial cells High Enhanced Q9H0G5 84081 +ENSG00000126653 NSRP1 lung macrophages Medium Enhanced Q9H0G5 84081 +ENSG00000126653 NSRP1 lung pneumocytes Medium Enhanced Q9H0G5 84081 +ENSG00000126746 ZNF384 bronchus respiratory epithelial cells High Supported Q8TF68 171017 +ENSG00000126746 ZNF384 lung macrophages Low Supported Q8TF68 171017 +ENSG00000126746 ZNF384 lung pneumocytes Medium Supported Q8TF68 171017 +ENSG00000126749 EMG1 bronchus respiratory epithelial cells Low Supported Q92979 10436 +ENSG00000126749 EMG1 lung macrophages Low Supported Q92979 10436 +ENSG00000126767 ELK1 bronchus respiratory epithelial cells Low Enhanced P19419 2002 +ENSG00000126767 ELK1 lung pneumocytes Low Enhanced P19419 2002 +ENSG00000126777 KTN1 bronchus respiratory epithelial cells High Enhanced Q86UP2 3895 +ENSG00000126777 KTN1 lung macrophages High Enhanced Q86UP2 3895 +ENSG00000126777 KTN1 lung pneumocytes High Enhanced Q86UP2 3895 +ENSG00000126778 SIX1 bronchus respiratory epithelial cells Medium Enhanced Q15475 6495 +ENSG00000126787 DLGAP5 bronchus respiratory epithelial cells Low Enhanced Q15398 9787 +ENSG00000126787 DLGAP5 lung macrophages Low Enhanced Q15398 9787 +ENSG00000126814 TRMT5 bronchus respiratory epithelial cells High Supported Q32P41 57570 +ENSG00000126814 TRMT5 lung macrophages High Supported Q32P41 57570 +ENSG00000126814 TRMT5 lung pneumocytes Low Supported Q32P41 57570 +ENSG00000126822 PLEKHG3 bronchus respiratory epithelial cells Medium Enhanced A1L390 26030 +ENSG00000126822 PLEKHG3 lung macrophages Low Enhanced A1L390 26030 +ENSG00000126838 PZP bronchus respiratory epithelial cells Medium Supported P20742 NA +ENSG00000126838 PZP lung macrophages High Supported P20742 NA +ENSG00000126838 PZP lung pneumocytes Low Supported P20742 NA +ENSG00000126858 RHOT1 bronchus respiratory epithelial cells High Enhanced Q8IXI2 55288 +ENSG00000126858 RHOT1 lung macrophages High Enhanced Q8IXI2 55288 +ENSG00000126858 RHOT1 lung pneumocytes Medium Enhanced Q8IXI2 55288 +ENSG00000126878 AIF1L lung macrophages Low Enhanced Q9BQI0 83543 +ENSG00000126934 MAP2K2 bronchus respiratory epithelial cells Medium Supported P36507 5605 +ENSG00000126934 MAP2K2 lung macrophages High Supported P36507 5605 +ENSG00000126934 MAP2K2 lung pneumocytes Low Supported P36507 5605 +ENSG00000126945 HNRNPH2 bronchus respiratory epithelial cells High Supported P55795 3188 +ENSG00000126945 HNRNPH2 lung macrophages Medium Supported P55795 3188 +ENSG00000126945 HNRNPH2 lung pneumocytes Medium Supported P55795 3188 +ENSG00000126947 ARMCX1 bronchus respiratory epithelial cells Medium Supported Q9P291 51309 +ENSG00000126947 ARMCX1 lung macrophages Medium Supported Q9P291 51309 +ENSG00000126947 ARMCX1 lung pneumocytes Low Supported Q9P291 51309 +ENSG00000126953 TIMM8A bronchus respiratory epithelial cells Medium Supported O60220 1678 +ENSG00000127022 CANX bronchus respiratory epithelial cells High Enhanced D6RB85 NA +ENSG00000127022 CANX lung macrophages High Enhanced D6RB85 NA +ENSG00000127022 CANX lung pneumocytes High Enhanced D6RB85 NA +ENSG00000127241 MASP1 bronchus respiratory epithelial cells Low Supported P48740 5648 +ENSG00000127241 MASP1 lung macrophages Low Supported P48740 5648 +ENSG00000127415 IDUA bronchus respiratory epithelial cells Medium Enhanced P35475 3425 +ENSG00000127415 IDUA lung macrophages Medium Enhanced P35475 3425 +ENSG00000127415 IDUA lung pneumocytes Medium Enhanced P35475 3425 +ENSG00000127483 HP1BP3 bronchus respiratory epithelial cells Medium Supported Q5SSJ5 50809 +ENSG00000127483 HP1BP3 lung pneumocytes Medium Supported Q5SSJ5 50809 +ENSG00000127616 SMARCA4 bronchus respiratory epithelial cells High Supported P51532 6597 +ENSG00000127616 SMARCA4 lung macrophages High Supported P51532 6597 +ENSG00000127616 SMARCA4 lung pneumocytes High Supported P51532 6597 +ENSG00000127884 ECHS1 bronchus respiratory epithelial cells High Enhanced P30084 1892 +ENSG00000127884 ECHS1 lung macrophages High Enhanced P30084 1892 +ENSG00000127884 ECHS1 lung pneumocytes Medium Enhanced P30084 1892 +ENSG00000127914 AKAP9 bronchus respiratory epithelial cells High Enhanced Q99996 10142 +ENSG00000127914 AKAP9 lung macrophages Medium Enhanced Q99996 10142 +ENSG00000127914 AKAP9 lung pneumocytes Medium Enhanced Q99996 10142 +ENSG00000127946 HIP1 bronchus respiratory epithelial cells Medium Enhanced O00291 3092 +ENSG00000127946 HIP1 lung macrophages Medium Enhanced O00291 3092 +ENSG00000127946 HIP1 lung pneumocytes High Enhanced O00291 3092 +ENSG00000127948 POR bronchus respiratory epithelial cells High Enhanced P16435 5447 +ENSG00000127948 POR lung macrophages High Enhanced P16435 5447 +ENSG00000127948 POR lung pneumocytes High Enhanced P16435 5447 +ENSG00000127951 FGL2 lung macrophages Low Enhanced Q14314 10875 +ENSG00000128309 MPST bronchus respiratory epithelial cells Medium Enhanced P25325 4357 +ENSG00000128309 MPST lung macrophages Medium Enhanced P25325 4357 +ENSG00000128309 MPST lung pneumocytes Medium Enhanced P25325 4357 +ENSG00000128311 TST bronchus respiratory epithelial cells High Enhanced Q16762 7263 +ENSG00000128311 TST lung macrophages Medium Enhanced Q16762 7263 +ENSG00000128311 TST lung pneumocytes Medium Enhanced Q16762 7263 +ENSG00000128422 KRT17 bronchus respiratory epithelial cells Medium Enhanced Q04695 3872 +ENSG00000128487 SPECC1 bronchus respiratory epithelial cells Medium Enhanced Q5M775 92521 +ENSG00000128487 SPECC1 lung macrophages Medium Enhanced Q5M775 92521 +ENSG00000128487 SPECC1 lung pneumocytes Medium Enhanced Q5M775 92521 +ENSG00000128524 ATP6V1F bronchus respiratory epithelial cells Medium Enhanced Q16864 9296 +ENSG00000128524 ATP6V1F lung macrophages High Enhanced Q16864 9296 +ENSG00000128524 ATP6V1F lung pneumocytes Low Enhanced Q16864 9296 +ENSG00000128573 FOXP2 bronchus respiratory epithelial cells Medium Enhanced O15409 93986 +ENSG00000128573 FOXP2 lung pneumocytes Low Enhanced O15409 93986 +ENSG00000128590 DNAJB9 bronchus respiratory epithelial cells Medium Supported Q9UBS3 4189 +ENSG00000128590 DNAJB9 lung macrophages Medium Supported Q9UBS3 4189 +ENSG00000128590 DNAJB9 lung pneumocytes Low Supported Q9UBS3 4189 +ENSG00000128591 FLNC lung macrophages High Enhanced Q14315 2318 +ENSG00000128595 CALU bronchus respiratory epithelial cells Low Supported O43852 813 +ENSG00000128595 CALU lung macrophages High Supported O43852 813 +ENSG00000128595 CALU lung pneumocytes Medium Supported O43852 813 +ENSG00000128609 NDUFA5 bronchus respiratory epithelial cells Medium Supported Q16718 4698 +ENSG00000128609 NDUFA5 lung macrophages Medium Supported Q16718 4698 +ENSG00000128609 NDUFA5 lung pneumocytes Low Supported Q16718 4698 +ENSG00000128708 HAT1 bronchus respiratory epithelial cells Medium Enhanced O14929 8520 +ENSG00000128833 MYO5C bronchus respiratory epithelial cells Medium Enhanced Q9NQX4 55930 +ENSG00000128833 MYO5C lung pneumocytes Medium Enhanced Q9NQX4 55930 +ENSG00000128849 CGNL1 lung pneumocytes Low Enhanced Q0VF96 84952 +ENSG00000128928 IVD bronchus respiratory epithelial cells High Enhanced P26440 3712 +ENSG00000128928 IVD lung macrophages High Enhanced P26440 3712 +ENSG00000128928 IVD lung pneumocytes Medium Enhanced P26440 3712 +ENSG00000128944 KNSTRN bronchus respiratory epithelial cells Low Enhanced Q9Y448 90417 +ENSG00000128944 KNSTRN lung macrophages Low Enhanced Q9Y448 90417 +ENSG00000128951 DUT bronchus respiratory epithelial cells Medium Enhanced P33316 1854 +ENSG00000128951 DUT lung macrophages Low Enhanced P33316 1854 +ENSG00000128951 DUT lung pneumocytes Low Enhanced P33316 1854 +ENSG00000129071 MBD4 bronchus respiratory epithelial cells Medium Supported O95243 8930 +ENSG00000129071 MBD4 lung macrophages Medium Supported O95243 8930 +ENSG00000129071 MBD4 lung pneumocytes Low Supported O95243 8930 +ENSG00000129083 COPB1 bronchus respiratory epithelial cells Medium Supported P53618 1315 +ENSG00000129083 COPB1 lung macrophages Low Supported P53618 1315 +ENSG00000129083 COPB1 lung pneumocytes Medium Supported P53618 1315 +ENSG00000129084 PSMA1 bronchus respiratory epithelial cells Medium Supported P25786 5682 +ENSG00000129084 PSMA1 lung macrophages Medium Supported P25786 5682 +ENSG00000129084 PSMA1 lung pneumocytes Medium Supported P25786 5682 +ENSG00000129103 SUMF2 bronchus respiratory epithelial cells Medium Enhanced Q8NBJ7 25870 +ENSG00000129103 SUMF2 lung macrophages Medium Enhanced Q8NBJ7 25870 +ENSG00000129116 PALLD lung macrophages Low Enhanced Q8WX93 23022 +ENSG00000129158 SERGEF bronchus respiratory epithelial cells High Supported Q9UGK8 26297 +ENSG00000129158 SERGEF lung macrophages Medium Supported Q9UGK8 26297 +ENSG00000129158 SERGEF lung pneumocytes Low Supported Q9UGK8 26297 +ENSG00000129167 TPH1 bronchus respiratory epithelial cells Medium Enhanced P17752 7166 +ENSG00000129167 TPH1 lung pneumocytes Low Enhanced P17752 7166 +ENSG00000129226 CD68 lung macrophages High Enhanced P34810 968 +ENSG00000129245 FXR2 bronchus respiratory epithelial cells High Supported P51116 9513 +ENSG00000129245 FXR2 lung macrophages Medium Supported P51116 9513 +ENSG00000129245 FXR2 lung pneumocytes Medium Supported P51116 9513 +ENSG00000129315 CCNT1 bronchus respiratory epithelial cells High Supported O60563 904 +ENSG00000129315 CCNT1 lung macrophages Medium Supported O60563 904 +ENSG00000129315 CCNT1 lung pneumocytes Medium Supported O60563 904 +ENSG00000129351 ILF3 lung macrophages High Supported Q12906 3609 +ENSG00000129351 ILF3 lung pneumocytes High Supported Q12906 3609 +ENSG00000129514 FOXA1 bronchus respiratory epithelial cells Medium Enhanced P55317 3169 +ENSG00000129538 RNASE1 bronchus respiratory epithelial cells Low Supported P07998 6035 +ENSG00000129654 FOXJ1 bronchus respiratory epithelial cells High Enhanced Q92949 2302 +ENSG00000130024 PHF10 bronchus respiratory epithelial cells High Supported Q8WUB8 55274 +ENSG00000130024 PHF10 lung macrophages Low Supported Q8WUB8 55274 +ENSG00000130024 PHF10 lung pneumocytes High Supported Q8WUB8 55274 +ENSG00000130066 SAT1 bronchus respiratory epithelial cells Medium Supported P21673 6303 +ENSG00000130066 SAT1 lung macrophages Medium Supported P21673 6303 +ENSG00000130066 SAT1 lung pneumocytes Low Supported P21673 6303 +ENSG00000130119 GNL3L bronchus respiratory epithelial cells Medium Supported Q9NVN8 54552 +ENSG00000130119 GNL3L lung macrophages Medium Supported Q9NVN8 54552 +ENSG00000130119 GNL3L lung pneumocytes Medium Supported Q9NVN8 54552 +ENSG00000130175 PRKCSH bronchus respiratory epithelial cells Medium Enhanced P14314 5589 +ENSG00000130175 PRKCSH lung macrophages High Enhanced P14314 5589 +ENSG00000130175 PRKCSH lung pneumocytes High Enhanced P14314 5589 +ENSG00000130202 NECTIN2 bronchus respiratory epithelial cells Low Enhanced Q92692 5819 +ENSG00000130202 NECTIN2 lung macrophages Medium Enhanced Q92692 5819 +ENSG00000130202 NECTIN2 lung pneumocytes Medium Enhanced Q92692 5819 +ENSG00000130204 TOMM40 bronchus respiratory epithelial cells Medium Supported O96008 10452 +ENSG00000130204 TOMM40 lung macrophages Medium Supported O96008 10452 +ENSG00000130204 TOMM40 lung pneumocytes Medium Supported O96008 10452 +ENSG00000130255 RPL36 bronchus respiratory epithelial cells High Supported Q9Y3U8 25873 +ENSG00000130255 RPL36 lung macrophages Medium Supported Q9Y3U8 25873 +ENSG00000130255 RPL36 lung pneumocytes Low Supported Q9Y3U8 25873 +ENSG00000130402 ACTN4 bronchus respiratory epithelial cells Medium Supported K7EP19 NA +ENSG00000130402 ACTN4 lung macrophages Medium Supported K7EP19 NA +ENSG00000130402 ACTN4 lung pneumocytes High Supported K7EP19 NA +ENSG00000130427 EPO bronchus respiratory epithelial cells Low Supported P01588 2056 +ENSG00000130427 EPO lung pneumocytes Low Supported P01588 2056 +ENSG00000130522 JUND bronchus respiratory epithelial cells Medium Supported P17535 3727 +ENSG00000130522 JUND lung macrophages Low Supported P17535 3727 +ENSG00000130522 JUND lung pneumocytes Medium Supported P17535 3727 +ENSG00000130529 TRPM4 bronchus respiratory epithelial cells Medium Enhanced Q8TD43 54795 +ENSG00000130529 TRPM4 lung macrophages Low Enhanced Q8TD43 54795 +ENSG00000130545 CRB3 bronchus respiratory epithelial cells Low Enhanced Q9BUF7 92359 +ENSG00000130545 CRB3 lung macrophages Medium Enhanced Q9BUF7 92359 +ENSG00000130592 LSP1 lung macrophages High Enhanced P33241 4046 +ENSG00000130699 TAF4 bronchus respiratory epithelial cells Medium Supported O00268 6874 +ENSG00000130699 TAF4 lung macrophages Medium Supported O00268 6874 +ENSG00000130699 TAF4 lung pneumocytes High Supported O00268 6874 +ENSG00000130706 ADRM1 bronchus respiratory epithelial cells Medium Supported Q16186 11047 +ENSG00000130706 ADRM1 lung macrophages Low Supported Q16186 11047 +ENSG00000130706 ADRM1 lung pneumocytes Low Supported Q16186 11047 +ENSG00000130707 ASS1 bronchus respiratory epithelial cells Medium Enhanced P00966 445 +ENSG00000130724 CHMP2A lung macrophages Medium Enhanced O43633 27243 +ENSG00000130724 CHMP2A lung pneumocytes Medium Enhanced O43633 27243 +ENSG00000130726 TRIM28 bronchus respiratory epithelial cells High Enhanced Q13263 10155 +ENSG00000130726 TRIM28 lung macrophages High Enhanced Q13263 10155 +ENSG00000130726 TRIM28 lung pneumocytes High Enhanced Q13263 10155 +ENSG00000130749 ZC3H4 bronchus respiratory epithelial cells Medium Supported Q9UPT8 23211 +ENSG00000130749 ZC3H4 lung macrophages Medium Supported Q9UPT8 23211 +ENSG00000130749 ZC3H4 lung pneumocytes Low Supported Q9UPT8 23211 +ENSG00000130764 LRRC47 bronchus respiratory epithelial cells High Enhanced Q8N1G4 57470 +ENSG00000130764 LRRC47 lung macrophages Medium Enhanced Q8N1G4 57470 +ENSG00000130764 LRRC47 lung pneumocytes Medium Enhanced Q8N1G4 57470 +ENSG00000130770 ATPIF1 bronchus respiratory epithelial cells High Supported Q9UII2 93974 +ENSG00000130770 ATPIF1 lung macrophages Medium Supported Q9UII2 93974 +ENSG00000130770 ATPIF1 lung pneumocytes High Supported Q9UII2 93974 +ENSG00000130787 HIP1R bronchus respiratory epithelial cells Medium Enhanced O75146 9026 +ENSG00000130787 HIP1R lung macrophages Low Enhanced O75146 9026 +ENSG00000130787 HIP1R lung pneumocytes Medium Enhanced O75146 9026 +ENSG00000130816 DNMT1 bronchus respiratory epithelial cells Low Enhanced P26358 1786 +ENSG00000130826 DKC1 bronchus respiratory epithelial cells High Supported O60832 1736 +ENSG00000130826 DKC1 lung macrophages High Supported O60832 1736 +ENSG00000130826 DKC1 lung pneumocytes High Supported O60832 1736 +ENSG00000130935 NOL11 bronchus respiratory epithelial cells High Supported Q9H8H0 25926 +ENSG00000130935 NOL11 lung macrophages Medium Supported Q9H8H0 25926 +ENSG00000130935 NOL11 lung pneumocytes Low Supported Q9H8H0 25926 +ENSG00000131016 AKAP12 lung macrophages Low Enhanced Q02952 9590 +ENSG00000131051 RBM39 bronchus respiratory epithelial cells Medium Supported Q14498 9584 +ENSG00000131051 RBM39 lung macrophages Medium Supported Q14498 9584 +ENSG00000131051 RBM39 lung pneumocytes High Supported Q14498 9584 +ENSG00000131100 ATP6V1E1 bronchus respiratory epithelial cells Medium Enhanced P36543 529 +ENSG00000131100 ATP6V1E1 lung macrophages High Enhanced P36543 529 +ENSG00000131143 COX4I1 bronchus respiratory epithelial cells Medium Supported P13073 1327 +ENSG00000131143 COX4I1 lung macrophages Medium Supported P13073 1327 +ENSG00000131238 PPT1 bronchus respiratory epithelial cells High Supported P50897 5538 +ENSG00000131238 PPT1 lung macrophages High Supported P50897 5538 +ENSG00000131238 PPT1 lung pneumocytes Low Supported P50897 5538 +ENSG00000131389 SLC6A6 bronchus respiratory epithelial cells Medium Enhanced P31641 6533 +ENSG00000131400 NAPSA lung macrophages High Enhanced O96009 9476 +ENSG00000131400 NAPSA lung pneumocytes Medium Enhanced O96009 9476 +ENSG00000131462 TUBG1 bronchus respiratory epithelial cells Medium Enhanced P23258 7283 +ENSG00000131462 TUBG1 lung macrophages Medium Enhanced P23258 7283 +ENSG00000131462 TUBG1 lung pneumocytes Medium Enhanced P23258 7283 +ENSG00000131467 PSME3 bronchus respiratory epithelial cells High Supported P61289 10197 +ENSG00000131467 PSME3 lung macrophages High Supported P61289 10197 +ENSG00000131467 PSME3 lung pneumocytes High Supported P61289 10197 +ENSG00000131471 AOC3 lung pneumocytes High Enhanced Q16853 8639 +ENSG00000131473 ACLY bronchus respiratory epithelial cells Medium Enhanced P53396 47 +ENSG00000131473 ACLY lung pneumocytes Low Enhanced P53396 47 +ENSG00000131482 G6PC lung macrophages Low Enhanced P35575 2538 +ENSG00000131711 MAP1B bronchus respiratory epithelial cells Medium Enhanced P46821 4131 +ENSG00000131747 TOP2A bronchus respiratory epithelial cells Low Enhanced P11388 7153 +ENSG00000131747 TOP2A lung pneumocytes Low Enhanced P11388 7153 +ENSG00000131773 KHDRBS3 bronchus respiratory epithelial cells Medium Enhanced O75525 10656 +ENSG00000131778 CHD1L bronchus respiratory epithelial cells High Enhanced Q86WJ1 9557 +ENSG00000131778 CHD1L lung macrophages Low Enhanced Q86WJ1 9557 +ENSG00000131778 CHD1L lung pneumocytes Low Enhanced Q86WJ1 9557 +ENSG00000131779 PEX11B bronchus respiratory epithelial cells Low Supported O96011 8799 +ENSG00000131779 PEX11B lung macrophages Low Supported O96011 8799 +ENSG00000131779 PEX11B lung pneumocytes High Supported O96011 8799 +ENSG00000131781 FMO5 lung macrophages Low Enhanced P49326 2330 +ENSG00000131844 MCCC2 bronchus respiratory epithelial cells Medium Enhanced Q9HCC0 64087 +ENSG00000131844 MCCC2 lung macrophages Medium Enhanced Q9HCC0 64087 +ENSG00000131844 MCCC2 lung pneumocytes Low Enhanced Q9HCC0 64087 +ENSG00000131876 SNRPA1 bronchus respiratory epithelial cells High Supported P09661 6627 +ENSG00000131876 SNRPA1 lung macrophages Medium Supported P09661 6627 +ENSG00000131876 SNRPA1 lung pneumocytes Medium Supported P09661 6627 +ENSG00000131899 LLGL1 bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000131899 LLGL1 lung macrophages Medium Enhanced NA NA +ENSG00000131899 LLGL1 lung pneumocytes Medium Enhanced NA NA +ENSG00000131914 LIN28A bronchus respiratory epithelial cells Low Enhanced Q9H9Z2 79727 +ENSG00000131914 LIN28A lung pneumocytes Low Enhanced Q9H9Z2 79727 +ENSG00000131981 LGALS3 bronchus respiratory epithelial cells Medium Enhanced P17931 3958 +ENSG00000131981 LGALS3 lung macrophages High Enhanced P17931 3958 +ENSG00000132002 DNAJB1 bronchus respiratory epithelial cells High Enhanced P25685 3337 +ENSG00000132002 DNAJB1 lung pneumocytes Medium Enhanced P25685 3337 +ENSG00000132024 CC2D1A bronchus respiratory epithelial cells Medium Supported Q6P1N0 54862 +ENSG00000132024 CC2D1A lung macrophages Medium Supported Q6P1N0 54862 +ENSG00000132024 CC2D1A lung pneumocytes Medium Supported Q6P1N0 54862 +ENSG00000132153 DHX30 bronchus respiratory epithelial cells Medium Supported Q7L2E3 22907 +ENSG00000132153 DHX30 lung macrophages High Supported Q7L2E3 22907 +ENSG00000132153 DHX30 lung pneumocytes Low Supported Q7L2E3 22907 +ENSG00000132185 FCRLA lung macrophages Low Enhanced Q7L513 84824 +ENSG00000132199 ENOSF1 bronchus respiratory epithelial cells High Enhanced Q7L5Y1 55556 +ENSG00000132199 ENOSF1 lung macrophages Medium Enhanced Q7L5Y1 55556 +ENSG00000132205 EMILIN2 bronchus respiratory epithelial cells Low Supported Q9BXX0 84034 +ENSG00000132205 EMILIN2 lung macrophages Low Supported Q9BXX0 84034 +ENSG00000132275 RRP8 lung macrophages Medium Supported O43159 23378 +ENSG00000132275 RRP8 lung pneumocytes Medium Supported O43159 23378 +ENSG00000132294 EFR3A bronchus respiratory epithelial cells Medium Enhanced Q14156 23167 +ENSG00000132294 EFR3A lung macrophages Medium Enhanced Q14156 23167 +ENSG00000132300 PTCD3 bronchus respiratory epithelial cells Medium Supported Q96EY7 55037 +ENSG00000132300 PTCD3 lung macrophages Medium Supported Q96EY7 55037 +ENSG00000132300 PTCD3 lung pneumocytes Low Supported Q96EY7 55037 +ENSG00000132305 IMMT bronchus respiratory epithelial cells Medium Enhanced Q16891 10989 +ENSG00000132305 IMMT lung macrophages Low Enhanced Q16891 10989 +ENSG00000132326 PER2 bronchus respiratory epithelial cells High Enhanced O15055 8864 +ENSG00000132326 PER2 lung macrophages High Enhanced O15055 8864 +ENSG00000132326 PER2 lung pneumocytes High Enhanced O15055 8864 +ENSG00000132334 PTPRE bronchus respiratory epithelial cells Medium Supported P23469 5791 +ENSG00000132334 PTPRE lung macrophages High Supported P23469 5791 +ENSG00000132334 PTPRE lung pneumocytes Medium Supported P23469 5791 +ENSG00000132356 PRKAA1 bronchus respiratory epithelial cells Medium Supported Q13131 5562 +ENSG00000132382 MYBBP1A bronchus respiratory epithelial cells High Supported Q9BQG0 10514 +ENSG00000132383 RPA1 bronchus respiratory epithelial cells High Supported P27694 6117 +ENSG00000132383 RPA1 lung macrophages Medium Supported P27694 6117 +ENSG00000132383 RPA1 lung pneumocytes Medium Supported P27694 6117 +ENSG00000132423 COQ3 bronchus respiratory epithelial cells Medium Enhanced Q9NZJ6 51805 +ENSG00000132437 DDC bronchus respiratory epithelial cells Low Enhanced P20711 1644 +ENSG00000132463 GRSF1 bronchus respiratory epithelial cells Medium Enhanced Q12849 2926 +ENSG00000132463 GRSF1 lung macrophages Medium Enhanced Q12849 2926 +ENSG00000132463 GRSF1 lung pneumocytes Low Enhanced Q12849 2926 +ENSG00000132465 JCHAIN bronchus respiratory epithelial cells Low Enhanced P01591 3512 +ENSG00000132465 JCHAIN lung macrophages Medium Enhanced P01591 3512 +ENSG00000132470 ITGB4 bronchus respiratory epithelial cells Low Enhanced P16144 3691 +ENSG00000132470 ITGB4 lung macrophages Low Enhanced P16144 3691 +ENSG00000132475 H3F3B bronchus respiratory epithelial cells High Supported K7EK07 NA +ENSG00000132475 H3F3B lung macrophages Medium Supported K7EK07 NA +ENSG00000132475 H3F3B lung pneumocytes High Supported K7EK07 NA +ENSG00000132485 ZRANB2 bronchus respiratory epithelial cells High Supported O95218 9406 +ENSG00000132485 ZRANB2 lung macrophages Medium Supported O95218 9406 +ENSG00000132485 ZRANB2 lung pneumocytes Medium Supported O95218 9406 +ENSG00000132510 KDM6B bronchus respiratory epithelial cells Medium Enhanced O15054 23135 +ENSG00000132510 KDM6B lung macrophages Medium Enhanced O15054 23135 +ENSG00000132510 KDM6B lung pneumocytes Low Enhanced O15054 23135 +ENSG00000132563 REEP2 lung pneumocytes Low Enhanced Q9BRK0 51308 +ENSG00000132589 FLOT2 bronchus respiratory epithelial cells Medium Enhanced Q14254 2319 +ENSG00000132589 FLOT2 lung macrophages Medium Enhanced Q14254 2319 +ENSG00000132589 FLOT2 lung pneumocytes Medium Enhanced Q14254 2319 +ENSG00000132591 ERAL1 bronchus respiratory epithelial cells Medium Supported O75616 26284 +ENSG00000132591 ERAL1 lung macrophages High Supported O75616 26284 +ENSG00000132591 ERAL1 lung pneumocytes Medium Supported O75616 26284 +ENSG00000132600 PRMT7 bronchus respiratory epithelial cells High Supported Q9NVM4 54496 +ENSG00000132600 PRMT7 lung macrophages High Supported Q9NVM4 54496 +ENSG00000132600 PRMT7 lung pneumocytes Medium Supported Q9NVM4 54496 +ENSG00000132603 NIP7 bronchus respiratory epithelial cells Medium Enhanced Q9Y221 51388 +ENSG00000132603 NIP7 lung macrophages Medium Enhanced Q9Y221 51388 +ENSG00000132603 NIP7 lung pneumocytes Medium Enhanced Q9Y221 51388 +ENSG00000132604 TERF2 bronchus respiratory epithelial cells Medium Enhanced Q15554 7014 +ENSG00000132604 TERF2 lung macrophages Medium Enhanced Q15554 7014 +ENSG00000132604 TERF2 lung pneumocytes Medium Enhanced Q15554 7014 +ENSG00000132646 PCNA bronchus respiratory epithelial cells Medium Enhanced P12004 5111 +ENSG00000132646 PCNA lung macrophages Low Enhanced P12004 5111 +ENSG00000132646 PCNA lung pneumocytes Low Enhanced P12004 5111 +ENSG00000132694 ARHGEF11 bronchus respiratory epithelial cells Medium Enhanced O15085 9826 +ENSG00000132694 ARHGEF11 lung macrophages High Enhanced O15085 9826 +ENSG00000132694 ARHGEF11 lung pneumocytes Low Enhanced O15085 9826 +ENSG00000132698 RAB25 bronchus respiratory epithelial cells High Enhanced P57735 57111 +ENSG00000132698 RAB25 lung pneumocytes High Enhanced P57735 57111 +ENSG00000132744 ACY3 lung macrophages Low Enhanced Q96HD9 91703 +ENSG00000132746 ALDH3B2 lung pneumocytes Low Enhanced P48448 NA +ENSG00000132773 TOE1 bronchus respiratory epithelial cells High Enhanced Q96GM8 114034 +ENSG00000132773 TOE1 lung macrophages High Enhanced Q96GM8 114034 +ENSG00000132773 TOE1 lung pneumocytes High Enhanced Q96GM8 114034 +ENSG00000132780 NASP bronchus respiratory epithelial cells Low Enhanced P49321 4678 +ENSG00000132938 MTUS2 bronchus respiratory epithelial cells Medium Enhanced Q5JR59 23281 +ENSG00000132938 MTUS2 lung macrophages Medium Enhanced Q5JR59 23281 +ENSG00000132938 MTUS2 lung pneumocytes Medium Enhanced Q5JR59 23281 +ENSG00000132965 ALOX5AP lung macrophages Medium Enhanced P20292 241 +ENSG00000133020 MYH8 lung macrophages Low Enhanced P13535 4626 +ENSG00000133026 MYH10 bronchus respiratory epithelial cells Medium Enhanced P35580 4628 +ENSG00000133026 MYH10 lung macrophages Low Enhanced P35580 4628 +ENSG00000133028 SCO1 bronchus respiratory epithelial cells Medium Enhanced O75880 6341 +ENSG00000133028 SCO1 lung macrophages Medium Enhanced O75880 6341 +ENSG00000133028 SCO1 lung pneumocytes Low Enhanced O75880 6341 +ENSG00000133030 MPRIP bronchus respiratory epithelial cells Medium Enhanced Q6WCQ1 23164 +ENSG00000133030 MPRIP lung macrophages Medium Enhanced Q6WCQ1 23164 +ENSG00000133030 MPRIP lung pneumocytes Low Enhanced Q6WCQ1 23164 +ENSG00000133110 POSTN bronchus respiratory epithelial cells High Enhanced Q15063 10631 +ENSG00000133110 POSTN lung macrophages Medium Enhanced Q15063 10631 +ENSG00000133110 POSTN lung pneumocytes Medium Enhanced Q15063 10631 +ENSG00000133115 STOML3 bronchus respiratory epithelial cells High Enhanced Q8TAV4 161003 +ENSG00000133121 STARD13 bronchus respiratory epithelial cells Medium Enhanced Q9Y3M8 90627 +ENSG00000133121 STARD13 lung pneumocytes Low Enhanced Q9Y3M8 90627 +ENSG00000133138 TBC1D8B bronchus respiratory epithelial cells Medium Enhanced Q0IIM8 54885 +ENSG00000133226 SRRM1 bronchus respiratory epithelial cells High Supported Q8IYB3 10250 +ENSG00000133226 SRRM1 lung macrophages Medium Supported Q8IYB3 10250 +ENSG00000133226 SRRM1 lung pneumocytes Medium Supported Q8IYB3 10250 +ENSG00000133265 HSPBP1 bronchus respiratory epithelial cells High Enhanced Q9NZL4 23640 +ENSG00000133265 HSPBP1 lung macrophages Medium Enhanced Q9NZL4 23640 +ENSG00000133265 HSPBP1 lung pneumocytes Medium Enhanced Q9NZL4 23640 +ENSG00000133313 CNDP2 bronchus respiratory epithelial cells Medium Enhanced Q96KP4 55748 +ENSG00000133313 CNDP2 lung macrophages Medium Enhanced Q96KP4 55748 +ENSG00000133313 CNDP2 lung pneumocytes Low Enhanced Q96KP4 55748 +ENSG00000133318 RTN3 bronchus respiratory epithelial cells Low Enhanced O95197 10313 +ENSG00000133318 RTN3 lung macrophages Low Enhanced O95197 10313 +ENSG00000133393 FOPNL bronchus respiratory epithelial cells High Supported NA NA +ENSG00000133393 FOPNL lung macrophages Medium Supported NA NA +ENSG00000133422 MORC2 bronchus respiratory epithelial cells Medium Enhanced Q9Y6X9 22880 +ENSG00000133422 MORC2 lung macrophages Medium Enhanced Q9Y6X9 22880 +ENSG00000133422 MORC2 lung pneumocytes Medium Enhanced Q9Y6X9 22880 +ENSG00000133574 GIMAP4 lung macrophages Medium Enhanced Q9NUV9 55303 +ENSG00000133661 SFTPD lung macrophages Medium Enhanced P35247 6441 +ENSG00000133661 SFTPD lung pneumocytes High Enhanced P35247 6441 +ENSG00000133665 DYDC2 bronchus respiratory epithelial cells High Enhanced Q96IM9 84332 +ENSG00000133706 LARS bronchus respiratory epithelial cells High Supported Q9P2J5 51520 +ENSG00000133706 LARS lung macrophages Low Supported Q9P2J5 51520 +ENSG00000133706 LARS lung pneumocytes Medium Supported Q9P2J5 51520 +ENSG00000133742 CA1 lung macrophages Low Enhanced P00915 759 +ENSG00000133789 SWAP70 lung macrophages Medium Supported Q9UH65 23075 +ENSG00000133794 ARNTL bronchus respiratory epithelial cells Medium Supported O00327 406 +ENSG00000133794 ARNTL lung macrophages Medium Supported O00327 406 +ENSG00000133794 ARNTL lung pneumocytes Medium Supported O00327 406 +ENSG00000133835 HSD17B4 bronchus respiratory epithelial cells Medium Enhanced P51659 3295 +ENSG00000133835 HSD17B4 lung macrophages Medium Enhanced P51659 3295 +ENSG00000133835 HSD17B4 lung pneumocytes High Enhanced P51659 3295 +ENSG00000133858 ZFC3H1 bronchus respiratory epithelial cells High Enhanced O60293 196441 +ENSG00000133858 ZFC3H1 lung macrophages Medium Enhanced O60293 196441 +ENSG00000133858 ZFC3H1 lung pneumocytes Medium Enhanced O60293 196441 +ENSG00000134001 EIF2S1 bronchus respiratory epithelial cells High Supported P05198 1965 +ENSG00000134001 EIF2S1 lung macrophages High Supported P05198 1965 +ENSG00000134001 EIF2S1 lung pneumocytes High Supported P05198 1965 +ENSG00000134049 IER3IP1 bronchus respiratory epithelial cells Medium Supported Q9Y5U9 51124 +ENSG00000134049 IER3IP1 lung macrophages Medium Supported Q9Y5U9 51124 +ENSG00000134049 IER3IP1 lung pneumocytes Low Supported Q9Y5U9 51124 +ENSG00000134056 MRPS36 bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000134056 MRPS36 lung macrophages High Supported NA NA +ENSG00000134056 MRPS36 lung pneumocytes Medium Supported NA NA +ENSG00000134057 CCNB1 bronchus respiratory epithelial cells Medium Enhanced P14635 891 +ENSG00000134058 CDK7 bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000134058 CDK7 lung macrophages High Enhanced NA NA +ENSG00000134058 CDK7 lung pneumocytes Medium Enhanced NA NA +ENSG00000134121 CHL1 bronchus respiratory epithelial cells Medium Enhanced O00533 10752 +ENSG00000134121 CHL1 lung macrophages Low Enhanced O00533 10752 +ENSG00000134138 MEIS2 bronchus respiratory epithelial cells High Enhanced O14770 4212 +ENSG00000134138 MEIS2 lung pneumocytes High Enhanced O14770 4212 +ENSG00000134240 HMGCS2 bronchus respiratory epithelial cells Low Enhanced P54868 3158 +ENSG00000134265 NAPG bronchus respiratory epithelial cells Low Enhanced Q99747 8774 +ENSG00000134265 NAPG lung macrophages Medium Enhanced Q99747 8774 +ENSG00000134265 NAPG lung pneumocytes Low Enhanced Q99747 8774 +ENSG00000134283 PPHLN1 bronchus respiratory epithelial cells Medium Enhanced Q8NEY8 51535 +ENSG00000134283 PPHLN1 lung macrophages Medium Enhanced Q8NEY8 51535 +ENSG00000134291 TMEM106C bronchus respiratory epithelial cells Medium Enhanced Q9BVX2 79022 +ENSG00000134291 TMEM106C lung macrophages Low Enhanced Q9BVX2 79022 +ENSG00000134313 KIDINS220 lung macrophages Medium Supported Q9ULH0 57498 +ENSG00000134317 GRHL1 bronchus respiratory epithelial cells Low Enhanced Q9NZI5 29841 +ENSG00000134317 GRHL1 lung macrophages Low Enhanced Q9NZI5 29841 +ENSG00000134317 GRHL1 lung pneumocytes Medium Enhanced Q9NZI5 29841 +ENSG00000134369 NAV1 bronchus respiratory epithelial cells Medium Enhanced Q8NEY1 89796 +ENSG00000134369 NAV1 lung macrophages Medium Enhanced Q8NEY1 89796 +ENSG00000134369 NAV1 lung pneumocytes Low Enhanced Q8NEY1 89796 +ENSG00000134371 CDC73 bronchus respiratory epithelial cells High Enhanced Q6P1J9 79577 +ENSG00000134371 CDC73 lung macrophages Low Enhanced Q6P1J9 79577 +ENSG00000134371 CDC73 lung pneumocytes Low Enhanced Q6P1J9 79577 +ENSG00000134419 RPS15A bronchus respiratory epithelial cells Medium Supported P62244 6210 +ENSG00000134419 RPS15A lung macrophages Medium Supported P62244 6210 +ENSG00000134419 RPS15A lung pneumocytes Low Supported P62244 6210 +ENSG00000134440 NARS bronchus respiratory epithelial cells Medium Enhanced O43776 4677 +ENSG00000134440 NARS lung macrophages Medium Enhanced O43776 4677 +ENSG00000134440 NARS lung pneumocytes Medium Enhanced O43776 4677 +ENSG00000134452 FBXO18 bronchus respiratory epithelial cells High Supported Q8NFZ0 84893 +ENSG00000134452 FBXO18 lung macrophages High Supported Q8NFZ0 84893 +ENSG00000134452 FBXO18 lung pneumocytes High Supported Q8NFZ0 84893 +ENSG00000134453 RBM17 bronchus respiratory epithelial cells High Supported Q96I25 84991 +ENSG00000134453 RBM17 lung macrophages High Supported Q96I25 84991 +ENSG00000134453 RBM17 lung pneumocytes High Supported Q96I25 84991 +ENSG00000134463 ECHDC3 bronchus respiratory epithelial cells Medium Enhanced Q96DC8 79746 +ENSG00000134463 ECHDC3 lung macrophages Medium Enhanced Q96DC8 79746 +ENSG00000134463 ECHDC3 lung pneumocytes Medium Enhanced Q96DC8 79746 +ENSG00000134516 DOCK2 lung macrophages Medium Enhanced Q92608 1794 +ENSG00000134574 DDB2 bronchus respiratory epithelial cells Medium Enhanced Q92466 1643 +ENSG00000134574 DDB2 lung macrophages Low Enhanced Q92466 1643 +ENSG00000134574 DDB2 lung pneumocytes Low Enhanced Q92466 1643 +ENSG00000134627 PIWIL4 bronchus respiratory epithelial cells Medium Enhanced Q7Z3Z4 143689 +ENSG00000134627 PIWIL4 lung macrophages Low Enhanced Q7Z3Z4 143689 +ENSG00000134627 PIWIL4 lung pneumocytes Medium Enhanced Q7Z3Z4 143689 +ENSG00000134668 SPOCD1 lung macrophages Low Enhanced Q6ZMY3 90853 +ENSG00000134684 YARS bronchus respiratory epithelial cells High Enhanced P54577 8565 +ENSG00000134684 YARS lung macrophages High Enhanced P54577 8565 +ENSG00000134684 YARS lung pneumocytes Medium Enhanced P54577 8565 +ENSG00000134686 PHC2 bronchus respiratory epithelial cells Medium Supported Q8IXK0 1912 +ENSG00000134686 PHC2 lung macrophages Medium Supported Q8IXK0 1912 +ENSG00000134686 PHC2 lung pneumocytes Medium Supported Q8IXK0 1912 +ENSG00000134744 ZCCHC11 lung macrophages Low Supported Q5TAX3 23318 +ENSG00000134744 ZCCHC11 lung pneumocytes Low Supported Q5TAX3 23318 +ENSG00000134755 DSC2 bronchus respiratory epithelial cells Low Enhanced Q02487 1824 +ENSG00000134755 DSC2 lung macrophages Low Enhanced Q02487 1824 +ENSG00000134760 DSG1 lung macrophages Medium Enhanced Q02413 1828 +ENSG00000134769 DTNA lung macrophages Low Enhanced Q9Y4J8 1837 +ENSG00000134809 TIMM10 bronchus respiratory epithelial cells High Enhanced P62072 26519 +ENSG00000134809 TIMM10 lung macrophages High Enhanced P62072 26519 +ENSG00000134809 TIMM10 lung pneumocytes Medium Enhanced P62072 26519 +ENSG00000134851 TMEM165 bronchus respiratory epithelial cells High Supported Q9HC07 55858 +ENSG00000134851 TMEM165 lung macrophages Medium Supported Q9HC07 55858 +ENSG00000134851 TMEM165 lung pneumocytes Medium Supported Q9HC07 55858 +ENSG00000134852 CLOCK bronchus respiratory epithelial cells Medium Supported O15516 9575 +ENSG00000134852 CLOCK lung macrophages Low Supported O15516 9575 +ENSG00000134852 CLOCK lung pneumocytes Medium Supported O15516 9575 +ENSG00000134871 COL4A2 lung pneumocytes High Enhanced P08572 1284 +ENSG00000134884 ARGLU1 bronchus respiratory epithelial cells High Supported Q9NWB6 55082 +ENSG00000134884 ARGLU1 lung macrophages Medium Supported Q9NWB6 55082 +ENSG00000134884 ARGLU1 lung pneumocytes Medium Supported Q9NWB6 55082 +ENSG00000134899 ERCC5 bronchus respiratory epithelial cells Medium Supported P28715 2073 +ENSG00000134899 ERCC5 lung macrophages Low Supported P28715 2073 +ENSG00000134899 ERCC5 lung pneumocytes Low Supported P28715 2073 +ENSG00000134970 TMED7 bronchus respiratory epithelial cells Medium Supported Q9Y3B3 100302736; 51014 +ENSG00000134970 TMED7 lung macrophages Medium Supported Q9Y3B3 100302736; 51014 +ENSG00000134970 TMED7 lung pneumocytes Low Supported Q9Y3B3 100302736; 51014 +ENSG00000134982 APC bronchus respiratory epithelial cells High Supported P25054 324 +ENSG00000134982 APC lung pneumocytes Low Supported P25054 324 +ENSG00000134987 WDR36 bronchus respiratory epithelial cells Medium Supported Q8NI36 134430 +ENSG00000134987 WDR36 lung macrophages Medium Supported Q8NI36 134430 +ENSG00000134987 WDR36 lung pneumocytes Low Supported Q8NI36 134430 +ENSG00000135018 UBQLN1 bronchus respiratory epithelial cells High Supported Q9UMX0 29979 +ENSG00000135018 UBQLN1 lung macrophages Medium Supported Q9UMX0 29979 +ENSG00000135018 UBQLN1 lung pneumocytes Low Supported Q9UMX0 29979 +ENSG00000135045 C9orf40 bronchus respiratory epithelial cells Medium Enhanced Q8IXQ3 55071 +ENSG00000135045 C9orf40 lung macrophages Medium Enhanced Q8IXQ3 55071 +ENSG00000135046 ANXA1 bronchus respiratory epithelial cells High Enhanced P04083 301 +ENSG00000135046 ANXA1 lung macrophages High Enhanced P04083 301 +ENSG00000135046 ANXA1 lung pneumocytes Medium Enhanced P04083 301 +ENSG00000135047 CTSL bronchus respiratory epithelial cells Low Enhanced P07711 1514 +ENSG00000135047 CTSL lung macrophages Medium Enhanced P07711 1514 +ENSG00000135052 GOLM1 bronchus respiratory epithelial cells Medium Enhanced Q8NBJ4 51280 +ENSG00000135052 GOLM1 lung macrophages Medium Enhanced Q8NBJ4 51280 +ENSG00000135077 HAVCR2 lung macrophages Low Enhanced Q8TDQ0 84868 +ENSG00000135124 P2RX4 bronchus respiratory epithelial cells Medium Enhanced Q99571 5025 +ENSG00000135124 P2RX4 lung macrophages High Enhanced Q99571 5025 +ENSG00000135127 BICDL1 bronchus respiratory epithelial cells Low Enhanced Q6ZP65 92558 +ENSG00000135127 BICDL1 lung macrophages Low Enhanced Q6ZP65 92558 +ENSG00000135164 DMTF1 bronchus respiratory epithelial cells High Supported Q9Y222 9988 +ENSG00000135164 DMTF1 lung macrophages Medium Supported Q9Y222 9988 +ENSG00000135164 DMTF1 lung pneumocytes Medium Supported Q9Y222 9988 +ENSG00000135299 ANKRD6 bronchus respiratory epithelial cells Medium Enhanced Q9Y2G4 22881 +ENSG00000135299 ANKRD6 lung macrophages Low Enhanced Q9Y2G4 22881 +ENSG00000135299 ANKRD6 lung pneumocytes Medium Enhanced Q9Y2G4 22881 +ENSG00000135315 CEP162 bronchus respiratory epithelial cells Medium Supported Q5TB80 22832 +ENSG00000135315 CEP162 lung macrophages Medium Supported Q5TB80 22832 +ENSG00000135315 CEP162 lung pneumocytes Low Supported Q5TB80 22832 +ENSG00000135316 SYNCRIP bronchus respiratory epithelial cells Medium Enhanced O60506 10492 +ENSG00000135316 SYNCRIP lung macrophages Low Enhanced O60506 10492 +ENSG00000135316 SYNCRIP lung pneumocytes Low Enhanced O60506 10492 +ENSG00000135336 ORC3 bronchus respiratory epithelial cells Medium Enhanced Q9UBD5 23595 +ENSG00000135336 ORC3 lung macrophages Medium Enhanced Q9UBD5 23595 +ENSG00000135336 ORC3 lung pneumocytes Medium Enhanced Q9UBD5 23595 +ENSG00000135338 LCA5 bronchus respiratory epithelial cells Medium Supported Q86VQ0 167691 +ENSG00000135338 LCA5 lung macrophages Medium Supported Q86VQ0 167691 +ENSG00000135338 LCA5 lung pneumocytes Low Supported Q86VQ0 167691 +ENSG00000135372 NAT10 lung macrophages Medium Enhanced Q9H0A0 55226 +ENSG00000135373 EHF bronchus respiratory epithelial cells Low Enhanced Q9NZC4 26298 +ENSG00000135373 EHF lung macrophages Low Enhanced Q9NZC4 26298 +ENSG00000135373 EHF lung pneumocytes Low Enhanced Q9NZC4 26298 +ENSG00000135404 CD63 bronchus respiratory epithelial cells Low Supported P08962 967 +ENSG00000135404 CD63 lung macrophages Medium Supported P08962 967 +ENSG00000135404 CD63 lung pneumocytes Medium Supported P08962 967 +ENSG00000135446 CDK4 bronchus respiratory epithelial cells Low Enhanced P11802 1019 +ENSG00000135480 KRT7 bronchus respiratory epithelial cells High Enhanced P08729 3855 +ENSG00000135480 KRT7 lung pneumocytes Medium Enhanced P08729 3855 +ENSG00000135486 HNRNPA1 bronchus respiratory epithelial cells High Supported P09651 3178 +ENSG00000135486 HNRNPA1 lung macrophages High Supported P09651 3178 +ENSG00000135486 HNRNPA1 lung pneumocytes High Supported P09651 3178 +ENSG00000135506 OS9 bronchus respiratory epithelial cells Medium Supported Q13438 10956 +ENSG00000135506 OS9 lung macrophages High Supported Q13438 10956 +ENSG00000135506 OS9 lung pneumocytes Medium Supported Q13438 10956 +ENSG00000135525 MAP7 bronchus respiratory epithelial cells High Enhanced Q14244 9053 +ENSG00000135525 MAP7 lung pneumocytes Low Enhanced Q14244 9053 +ENSG00000135677 GNS bronchus respiratory epithelial cells Medium Enhanced P15586 2799 +ENSG00000135677 GNS lung macrophages High Enhanced P15586 2799 +ENSG00000135677 GNS lung pneumocytes Low Enhanced P15586 2799 +ENSG00000135679 MDM2 bronchus respiratory epithelial cells High Supported Q00987 4193 +ENSG00000135679 MDM2 lung macrophages High Supported Q00987 4193 +ENSG00000135679 MDM2 lung pneumocytes High Supported Q00987 4193 +ENSG00000135736 CCDC102A bronchus respiratory epithelial cells Medium Supported Q96A19 92922 +ENSG00000135736 CCDC102A lung macrophages Low Supported Q96A19 92922 +ENSG00000135736 CCDC102A lung pneumocytes Low Supported Q96A19 92922 +ENSG00000135744 AGT bronchus respiratory epithelial cells Low Supported P01019 183 +ENSG00000135744 AGT lung macrophages Low Supported P01019 183 +ENSG00000135773 CAPN9 bronchus respiratory epithelial cells Low Enhanced O14815 10753 +ENSG00000135773 CAPN9 lung macrophages Low Enhanced O14815 10753 +ENSG00000135773 CAPN9 lung pneumocytes Low Enhanced O14815 10753 +ENSG00000135829 DHX9 bronchus respiratory epithelial cells Medium Supported Q08211 1660 +ENSG00000135829 DHX9 lung macrophages Medium Supported Q08211 1660 +ENSG00000135829 DHX9 lung pneumocytes Medium Supported Q08211 1660 +ENSG00000135837 CEP350 bronchus respiratory epithelial cells High Enhanced Q5VT06 9857 +ENSG00000135837 CEP350 lung macrophages Medium Enhanced Q5VT06 9857 +ENSG00000135837 CEP350 lung pneumocytes High Enhanced Q5VT06 9857 +ENSG00000135862 LAMC1 lung pneumocytes Medium Enhanced P11047 3915 +ENSG00000135905 DOCK10 lung macrophages Medium Enhanced Q96BY6 55619 +ENSG00000135914 HTR2B bronchus respiratory epithelial cells Medium Enhanced P41595 3357 +ENSG00000135914 HTR2B lung pneumocytes Low Enhanced P41595 3357 +ENSG00000135929 CYP27A1 bronchus respiratory epithelial cells High Enhanced Q02318 1593 +ENSG00000135929 CYP27A1 lung macrophages High Enhanced Q02318 1593 +ENSG00000135932 CAB39 bronchus respiratory epithelial cells High Supported Q9Y376 51719 +ENSG00000135932 CAB39 lung macrophages Medium Supported Q9Y376 51719 +ENSG00000135932 CAB39 lung pneumocytes Medium Supported Q9Y376 51719 +ENSG00000135940 COX5B bronchus respiratory epithelial cells High Supported P10606 1329 +ENSG00000135940 COX5B lung macrophages High Supported P10606 1329 +ENSG00000135940 COX5B lung pneumocytes High Supported P10606 1329 +ENSG00000135968 GCC2 bronchus respiratory epithelial cells High Enhanced Q8IWJ2 9648 +ENSG00000135968 GCC2 lung macrophages Medium Enhanced Q8IWJ2 9648 +ENSG00000135968 GCC2 lung pneumocytes Medium Enhanced Q8IWJ2 9648 +ENSG00000135972 MRPS9 bronchus respiratory epithelial cells High Enhanced P82933 64965 +ENSG00000135972 MRPS9 lung macrophages Medium Enhanced P82933 64965 +ENSG00000135972 MRPS9 lung pneumocytes Low Enhanced P82933 64965 +ENSG00000136026 CKAP4 bronchus respiratory epithelial cells High Enhanced Q07065 10970 +ENSG00000136026 CKAP4 lung macrophages Low Enhanced Q07065 10970 +ENSG00000136026 CKAP4 lung pneumocytes Low Enhanced Q07065 10970 +ENSG00000136059 VILL bronchus respiratory epithelial cells High Enhanced O15195 50853 +ENSG00000136068 FLNB bronchus respiratory epithelial cells High Enhanced O75369 2317 +ENSG00000136068 FLNB lung macrophages Medium Enhanced O75369 2317 +ENSG00000136068 FLNB lung pneumocytes High Enhanced O75369 2317 +ENSG00000136098 NEK3 bronchus respiratory epithelial cells Medium Enhanced P51956 4752 +ENSG00000136098 NEK3 lung pneumocytes Medium Enhanced P51956 4752 +ENSG00000136108 CKAP2 lung macrophages Low Enhanced Q8WWK9 26586 +ENSG00000136143 SUCLA2 bronchus respiratory epithelial cells Medium Enhanced Q9P2R7 8803 +ENSG00000136143 SUCLA2 lung macrophages Medium Enhanced Q9P2R7 8803 +ENSG00000136143 SUCLA2 lung pneumocytes Medium Enhanced Q9P2R7 8803 +ENSG00000136155 SCEL lung pneumocytes High Enhanced O95171 8796 +ENSG00000136167 LCP1 lung macrophages High Enhanced P13796 3936 +ENSG00000136193 SCRN1 bronchus respiratory epithelial cells Low Enhanced Q12765 9805 +ENSG00000136279 DBNL bronchus respiratory epithelial cells Medium Enhanced Q9UJU6 28988 +ENSG00000136279 DBNL lung macrophages Low Enhanced Q9UJU6 28988 +ENSG00000136280 CCM2 lung macrophages Medium Enhanced Q9BSQ5 83605 +ENSG00000136286 MYO1G lung macrophages Medium Enhanced B0I1T2 64005 +ENSG00000136352 NKX2-1 bronchus respiratory epithelial cells Low Enhanced P43699 7080 +ENSG00000136352 NKX2-1 lung macrophages Low Enhanced P43699 7080 +ENSG00000136352 NKX2-1 lung pneumocytes Medium Enhanced P43699 7080 +ENSG00000136436 CALCOCO2 bronchus respiratory epithelial cells Low Enhanced Q13137 10241 +ENSG00000136436 CALCOCO2 lung macrophages Medium Enhanced Q13137 10241 +ENSG00000136436 CALCOCO2 lung pneumocytes Low Enhanced Q13137 10241 +ENSG00000136448 NMT1 bronchus respiratory epithelial cells High Enhanced P30419 4836 +ENSG00000136448 NMT1 lung macrophages Medium Enhanced P30419 4836 +ENSG00000136448 NMT1 lung pneumocytes Low Enhanced P30419 4836 +ENSG00000136449 MYCBPAP bronchus respiratory epithelial cells Medium Enhanced Q8TBZ2 84073 +ENSG00000136450 SRSF1 bronchus respiratory epithelial cells High Supported Q07955 6426 +ENSG00000136450 SRSF1 lung macrophages Medium Supported Q07955 6426 +ENSG00000136450 SRSF1 lung pneumocytes Medium Supported Q07955 6426 +ENSG00000136457 CHAD bronchus respiratory epithelial cells Low Enhanced O15335 1101 +ENSG00000136463 TACO1 bronchus respiratory epithelial cells Medium Enhanced Q9BSH4 51204 +ENSG00000136463 TACO1 lung macrophages Medium Enhanced Q9BSH4 51204 +ENSG00000136463 TACO1 lung pneumocytes Low Enhanced Q9BSH4 51204 +ENSG00000136485 DCAF7 bronchus respiratory epithelial cells Medium Enhanced P61962 10238 +ENSG00000136485 DCAF7 lung macrophages Medium Enhanced P61962 10238 +ENSG00000136518 ACTL6A bronchus respiratory epithelial cells High Supported O96019 86 +ENSG00000136518 ACTL6A lung macrophages High Supported O96019 86 +ENSG00000136518 ACTL6A lung pneumocytes High Supported O96019 86 +ENSG00000136521 NDUFB5 bronchus respiratory epithelial cells Medium Enhanced O43674 4711 +ENSG00000136521 NDUFB5 lung macrophages Medium Enhanced O43674 4711 +ENSG00000136527 TRA2B bronchus respiratory epithelial cells High Supported P62995 6434 +ENSG00000136527 TRA2B lung macrophages High Supported P62995 6434 +ENSG00000136527 TRA2B lung pneumocytes High Supported P62995 6434 +ENSG00000136536 MARCH7 bronchus respiratory epithelial cells Medium Enhanced Q9H992 64844 +ENSG00000136536 MARCH7 lung macrophages High Enhanced Q9H992 64844 +ENSG00000136536 MARCH7 lung pneumocytes Low Enhanced Q9H992 64844 +ENSG00000136628 EPRS lung macrophages Medium Enhanced P07814 2058 +ENSG00000136628 EPRS lung pneumocytes Low Enhanced P07814 2058 +ENSG00000136709 WDR33 bronchus respiratory epithelial cells Medium Supported Q9C0J8 55339 +ENSG00000136709 WDR33 lung macrophages Medium Supported Q9C0J8 55339 +ENSG00000136709 WDR33 lung pneumocytes Medium Supported Q9C0J8 55339 +ENSG00000136717 BIN1 bronchus respiratory epithelial cells Medium Enhanced O00499 274 +ENSG00000136717 BIN1 lung macrophages Medium Enhanced O00499 274 +ENSG00000136717 BIN1 lung pneumocytes Medium Enhanced O00499 274 +ENSG00000136731 UGGT1 bronchus respiratory epithelial cells Medium Enhanced Q9NYU2 56886 +ENSG00000136731 UGGT1 lung macrophages High Enhanced Q9NYU2 56886 +ENSG00000136731 UGGT1 lung pneumocytes Low Enhanced Q9NYU2 56886 +ENSG00000136732 GYPC bronchus respiratory epithelial cells Medium Enhanced P04921 2995 +ENSG00000136732 GYPC lung macrophages Low Enhanced P04921 2995 +ENSG00000136732 GYPC lung pneumocytes Low Enhanced P04921 2995 +ENSG00000136738 STAM bronchus respiratory epithelial cells Medium Supported Q92783 8027 +ENSG00000136738 STAM lung macrophages Medium Supported Q92783 8027 +ENSG00000136807 CDK9 bronchus respiratory epithelial cells High Supported P50750 1025 +ENSG00000136807 CDK9 lung macrophages High Supported P50750 1025 +ENSG00000136807 CDK9 lung pneumocytes High Supported P50750 1025 +ENSG00000136810 TXN bronchus respiratory epithelial cells Medium Enhanced P10599 7295 +ENSG00000136810 TXN lung macrophages Low Enhanced P10599 7295 +ENSG00000136810 TXN lung pneumocytes Low Enhanced P10599 7295 +ENSG00000136819 C9orf78 bronchus respiratory epithelial cells High Enhanced Q9NZ63 51759 +ENSG00000136819 C9orf78 lung macrophages Low Enhanced Q9NZ63 51759 +ENSG00000136819 C9orf78 lung pneumocytes Medium Enhanced Q9NZ63 51759 +ENSG00000136826 KLF4 bronchus respiratory epithelial cells High Enhanced O43474 9314 +ENSG00000136826 KLF4 lung macrophages Low Enhanced O43474 9314 +ENSG00000136875 PRPF4 bronchus respiratory epithelial cells High Enhanced O43172 9128 +ENSG00000136875 PRPF4 lung macrophages Medium Enhanced O43172 9128 +ENSG00000136875 PRPF4 lung pneumocytes Medium Enhanced O43172 9128 +ENSG00000136888 ATP6V1G1 bronchus respiratory epithelial cells Medium Supported O75348 9550 +ENSG00000136888 ATP6V1G1 lung macrophages High Supported O75348 9550 +ENSG00000136888 ATP6V1G1 lung pneumocytes Medium Supported O75348 9550 +ENSG00000136930 PSMB7 bronchus respiratory epithelial cells High Enhanced Q99436 5695 +ENSG00000136930 PSMB7 lung macrophages Low Enhanced Q99436 5695 +ENSG00000136930 PSMB7 lung pneumocytes Low Enhanced Q99436 5695 +ENSG00000136933 RABEPK bronchus respiratory epithelial cells Medium Enhanced Q7Z6M1 10244 +ENSG00000136933 RABEPK lung macrophages Medium Enhanced Q7Z6M1 10244 +ENSG00000136933 RABEPK lung pneumocytes Low Enhanced Q7Z6M1 10244 +ENSG00000136935 GOLGA1 bronchus respiratory epithelial cells High Enhanced Q92805 2800 +ENSG00000136935 GOLGA1 lung macrophages Medium Enhanced Q92805 2800 +ENSG00000136935 GOLGA1 lung pneumocytes Medium Enhanced Q92805 2800 +ENSG00000136936 XPA bronchus respiratory epithelial cells High Supported P23025 7507 +ENSG00000136936 XPA lung macrophages Medium Supported P23025 7507 +ENSG00000136936 XPA lung pneumocytes Low Supported P23025 7507 +ENSG00000136937 NCBP1 bronchus respiratory epithelial cells High Enhanced Q09161 4686 +ENSG00000136937 NCBP1 lung macrophages High Enhanced Q09161 4686 +ENSG00000136937 NCBP1 lung pneumocytes Medium Enhanced Q09161 4686 +ENSG00000136938 ANP32B bronchus respiratory epithelial cells High Supported Q92688 10541 +ENSG00000136938 ANP32B lung macrophages Medium Supported Q92688 10541 +ENSG00000136938 ANP32B lung pneumocytes High Supported Q92688 10541 +ENSG00000136986 DERL1 bronchus respiratory epithelial cells Medium Enhanced Q9BUN8 79139 +ENSG00000136986 DERL1 lung macrophages Medium Enhanced Q9BUN8 79139 +ENSG00000136986 DERL1 lung pneumocytes Low Enhanced Q9BUN8 79139 +ENSG00000136997 MYC bronchus respiratory epithelial cells Medium Supported P01106 4609 +ENSG00000136997 MYC lung macrophages Medium Supported P01106 4609 +ENSG00000136997 MYC lung pneumocytes High Supported P01106 4609 +ENSG00000137033 IL33 bronchus respiratory epithelial cells High Supported O95760 90865 +ENSG00000137033 IL33 lung macrophages Low Supported O95760 90865 +ENSG00000137054 POLR1E lung macrophages Low Supported Q9GZS1 64425 +ENSG00000137070 IL11RA bronchus respiratory epithelial cells Medium Supported Q14626 3590 +ENSG00000137070 IL11RA lung macrophages Medium Supported Q14626 3590 +ENSG00000137074 APTX bronchus respiratory epithelial cells High Supported Q7Z2E3 54840 +ENSG00000137074 APTX lung macrophages Low Supported Q7Z2E3 54840 +ENSG00000137074 APTX lung pneumocytes High Supported Q7Z2E3 54840 +ENSG00000137076 TLN1 bronchus respiratory epithelial cells High Supported Q9Y490 7094 +ENSG00000137076 TLN1 lung macrophages High Supported Q9Y490 7094 +ENSG00000137076 TLN1 lung pneumocytes Medium Supported Q9Y490 7094 +ENSG00000137078 SIT1 bronchus respiratory epithelial cells Low Enhanced Q9Y3P8 27240 +ENSG00000137078 SIT1 lung pneumocytes Low Enhanced Q9Y3P8 27240 +ENSG00000137098 SPAG8 bronchus respiratory epithelial cells High Enhanced Q99932 26206 +ENSG00000137098 SPAG8 lung macrophages Low Enhanced Q99932 26206 +ENSG00000137133 HINT2 bronchus respiratory epithelial cells High Enhanced Q9BX68 84681 +ENSG00000137133 HINT2 lung macrophages Low Enhanced Q9BX68 84681 +ENSG00000137133 HINT2 lung pneumocytes Low Enhanced Q9BX68 84681 +ENSG00000137154 RPS6 bronchus respiratory epithelial cells High Supported P62753 6194 +ENSG00000137154 RPS6 lung macrophages Medium Supported P62753 6194 +ENSG00000137154 RPS6 lung pneumocytes Low Supported P62753 6194 +ENSG00000137171 KLC4 bronchus respiratory epithelial cells High Enhanced Q9NSK0 89953 +ENSG00000137171 KLC4 lung macrophages Medium Enhanced Q9NSK0 89953 +ENSG00000137200 CMTR1 bronchus respiratory epithelial cells High Enhanced Q8N1G2 23070 +ENSG00000137200 CMTR1 lung macrophages Low Enhanced Q8N1G2 23070 +ENSG00000137200 CMTR1 lung pneumocytes Low Enhanced Q8N1G2 23070 +ENSG00000137207 YIPF3 bronchus respiratory epithelial cells High Supported Q9GZM5 25844 +ENSG00000137207 YIPF3 lung macrophages Medium Supported Q9GZM5 25844 +ENSG00000137207 YIPF3 lung pneumocytes Medium Supported Q9GZM5 25844 +ENSG00000137218 FRS3 bronchus respiratory epithelial cells Medium Enhanced O43559 10817 +ENSG00000137221 TJAP1 bronchus respiratory epithelial cells Medium Supported Q5JTD0 93643 +ENSG00000137221 TJAP1 lung macrophages Low Supported Q5JTD0 93643 +ENSG00000137221 TJAP1 lung pneumocytes Low Supported Q5JTD0 93643 +ENSG00000137265 IRF4 lung macrophages Low Enhanced Q15306 3662 +ENSG00000137267 TUBB2A bronchus respiratory epithelial cells Low Supported Q13885 7280 +ENSG00000137269 LRRC1 bronchus respiratory epithelial cells Medium Enhanced Q9BTT6 55227 +ENSG00000137269 LRRC1 lung macrophages Medium Enhanced Q9BTT6 55227 +ENSG00000137269 LRRC1 lung pneumocytes Low Enhanced Q9BTT6 55227 +ENSG00000137274 BPHL bronchus respiratory epithelial cells Medium Enhanced Q86WA6 670 +ENSG00000137274 BPHL lung macrophages Low Enhanced Q86WA6 670 +ENSG00000137275 RIPK1 bronchus respiratory epithelial cells Medium Enhanced Q13546 8737 +ENSG00000137275 RIPK1 lung macrophages Low Enhanced Q13546 8737 +ENSG00000137275 RIPK1 lung pneumocytes Low Enhanced Q13546 8737 +ENSG00000137285 TUBB2B bronchus respiratory epithelial cells Low Supported Q9BVA1 347733 +ENSG00000137312 FLOT1 bronchus respiratory epithelial cells High Enhanced NA NA +ENSG00000137312 FLOT1 lung macrophages High Enhanced NA NA +ENSG00000137312 FLOT1 lung pneumocytes Low Enhanced NA NA +ENSG00000137337 MDC1 bronchus respiratory epithelial cells High Enhanced NA NA +ENSG00000137337 MDC1 lung macrophages Medium Enhanced NA NA +ENSG00000137337 MDC1 lung pneumocytes High Enhanced NA NA +ENSG00000137413 TAF8 bronchus respiratory epithelial cells Medium Supported Q7Z7C8 129685 +ENSG00000137413 TAF8 lung macrophages Medium Supported Q7Z7C8 129685 +ENSG00000137413 TAF8 lung pneumocytes Low Supported Q7Z7C8 129685 +ENSG00000137497 NUMA1 bronchus respiratory epithelial cells High Enhanced Q14980 4926 +ENSG00000137497 NUMA1 lung macrophages High Enhanced Q14980 4926 +ENSG00000137497 NUMA1 lung pneumocytes High Enhanced Q14980 4926 +ENSG00000137500 CCDC90B bronchus respiratory epithelial cells Medium Enhanced Q9GZT6 60492 +ENSG00000137500 CCDC90B lung macrophages Medium Enhanced Q9GZT6 60492 +ENSG00000137500 CCDC90B lung pneumocytes Medium Enhanced Q9GZT6 60492 +ENSG00000137513 NARS2 bronchus respiratory epithelial cells Medium Supported Q96I59 79731 +ENSG00000137513 NARS2 lung macrophages Medium Supported Q96I59 79731 +ENSG00000137513 NARS2 lung pneumocytes Medium Supported Q96I59 79731 +ENSG00000137547 MRPL15 bronchus respiratory epithelial cells Medium Enhanced Q9P015 29088 +ENSG00000137547 MRPL15 lung macrophages Low Enhanced Q9P015 29088 +ENSG00000137547 MRPL15 lung pneumocytes Medium Enhanced Q9P015 29088 +ENSG00000137573 SULF1 bronchus respiratory epithelial cells Low Supported Q8IWU6 23213 +ENSG00000137573 SULF1 lung pneumocytes Low Supported Q8IWU6 23213 +ENSG00000137574 TGS1 bronchus respiratory epithelial cells High Supported Q96RS0 96764 +ENSG00000137574 TGS1 lung macrophages High Supported Q96RS0 96764 +ENSG00000137574 TGS1 lung pneumocytes High Supported Q96RS0 96764 +ENSG00000137656 BUD13 bronchus respiratory epithelial cells Medium Enhanced Q9BRD0 84811 +ENSG00000137656 BUD13 lung macrophages Medium Enhanced Q9BRD0 84811 +ENSG00000137656 BUD13 lung pneumocytes Low Enhanced Q9BRD0 84811 +ENSG00000137673 MMP7 lung macrophages Low Supported P09237 4316 +ENSG00000137691 C11orf70 bronchus respiratory epithelial cells Low Enhanced Q9BRQ4 85016 +ENSG00000137693 YAP1 bronchus respiratory epithelial cells Medium Enhanced P46937 10413 +ENSG00000137693 YAP1 lung macrophages Medium Enhanced P46937 10413 +ENSG00000137693 YAP1 lung pneumocytes Medium Enhanced P46937 10413 +ENSG00000137699 TRIM29 bronchus respiratory epithelial cells Medium Enhanced Q14134 23650 +ENSG00000137699 TRIM29 lung pneumocytes Low Enhanced Q14134 23650 +ENSG00000137700 SLC37A4 bronchus respiratory epithelial cells Medium Enhanced U3KPU7 NA +ENSG00000137710 RDX bronchus respiratory epithelial cells Low Enhanced P35241 5962 +ENSG00000137764 MAP2K5 bronchus respiratory epithelial cells Medium Supported Q13163 5607 +ENSG00000137764 MAP2K5 lung macrophages Medium Supported Q13163 5607 +ENSG00000137764 MAP2K5 lung pneumocytes Low Supported Q13163 5607 +ENSG00000137767 SQRDL bronchus respiratory epithelial cells Medium Enhanced Q9Y6N5 58472 +ENSG00000137767 SQRDL lung macrophages Medium Enhanced Q9Y6N5 58472 +ENSG00000137776 SLTM lung macrophages High Enhanced Q9NWH9 79811 +ENSG00000137776 SLTM lung pneumocytes High Enhanced Q9NWH9 79811 +ENSG00000137802 MAPKBP1 bronchus respiratory epithelial cells Medium Enhanced O60336 23005 +ENSG00000137802 MAPKBP1 lung macrophages Low Enhanced O60336 23005 +ENSG00000137804 NUSAP1 bronchus respiratory epithelial cells Low Enhanced Q9BXS6 51203 +ENSG00000137806 NDUFAF1 bronchus respiratory epithelial cells High Supported Q9Y375 51103 +ENSG00000137806 NDUFAF1 lung macrophages High Supported Q9Y375 51103 +ENSG00000137806 NDUFAF1 lung pneumocytes High Supported Q9Y375 51103 +ENSG00000137812 KNL1 bronchus respiratory epithelial cells Low Supported Q8NG31 57082 +ENSG00000137824 RMDN3 bronchus respiratory epithelial cells High Supported Q96TC7 55177 +ENSG00000137824 RMDN3 lung macrophages High Supported Q96TC7 55177 +ENSG00000137824 RMDN3 lung pneumocytes Medium Supported Q96TC7 55177 +ENSG00000137876 RSL24D1 bronchus respiratory epithelial cells Low Enhanced Q9UHA3 51187 +ENSG00000137876 RSL24D1 lung pneumocytes Low Enhanced Q9UHA3 51187 +ENSG00000137944 KYAT3 bronchus respiratory epithelial cells Medium Enhanced Q6YP21 56267 +ENSG00000137944 KYAT3 lung macrophages Medium Enhanced Q6YP21 56267 +ENSG00000137944 KYAT3 lung pneumocytes Low Enhanced Q6YP21 56267 +ENSG00000137947 GTF2B bronchus respiratory epithelial cells High Enhanced Q00403 2959 +ENSG00000137947 GTF2B lung pneumocytes Medium Enhanced Q00403 2959 +ENSG00000137959 IFI44L bronchus respiratory epithelial cells Medium Enhanced Q53G44 10964 +ENSG00000137992 DBT bronchus respiratory epithelial cells Medium Enhanced P11182 1629 +ENSG00000137992 DBT lung macrophages Low Enhanced P11182 1629 +ENSG00000137992 DBT lung pneumocytes Low Enhanced P11182 1629 +ENSG00000138029 HADHB bronchus respiratory epithelial cells Low Enhanced P55084 3032 +ENSG00000138029 HADHB lung macrophages Medium Enhanced P55084 3032 +ENSG00000138029 HADHB lung pneumocytes Low Enhanced P55084 3032 +ENSG00000138035 PNPT1 bronchus respiratory epithelial cells High Supported Q8TCS8 87178 +ENSG00000138035 PNPT1 lung macrophages Medium Supported Q8TCS8 87178 +ENSG00000138035 PNPT1 lung pneumocytes Low Supported Q8TCS8 87178 +ENSG00000138095 LRPPRC bronchus respiratory epithelial cells High Enhanced P42704 10128 +ENSG00000138095 LRPPRC lung macrophages Medium Enhanced P42704 10128 +ENSG00000138095 LRPPRC lung pneumocytes Medium Enhanced P42704 10128 +ENSG00000138119 MYOF bronchus respiratory epithelial cells Medium Enhanced Q9NZM1 26509 +ENSG00000138119 MYOF lung macrophages High Enhanced Q9NZM1 26509 +ENSG00000138119 MYOF lung pneumocytes Medium Enhanced Q9NZM1 26509 +ENSG00000138160 KIF11 bronchus respiratory epithelial cells Medium Enhanced P52732 3832 +ENSG00000138160 KIF11 lung macrophages Low Enhanced P52732 3832 +ENSG00000138160 KIF11 lung pneumocytes Low Enhanced P52732 3832 +ENSG00000138162 TACC2 bronchus respiratory epithelial cells Low Enhanced O95359 10579 +ENSG00000138162 TACC2 lung macrophages Medium Enhanced O95359 10579 +ENSG00000138162 TACC2 lung pneumocytes Low Enhanced O95359 10579 +ENSG00000138185 ENTPD1 bronchus respiratory epithelial cells Medium Enhanced P49961 953 +ENSG00000138185 ENTPD1 lung macrophages Low Enhanced P49961 953 +ENSG00000138193 PLCE1 bronchus respiratory epithelial cells Medium Enhanced Q9P212 51196 +ENSG00000138193 PLCE1 lung macrophages Medium Enhanced Q9P212 51196 +ENSG00000138231 DBR1 bronchus respiratory epithelial cells Medium Supported Q9UK59 51163 +ENSG00000138231 DBR1 lung macrophages Medium Supported Q9UK59 51163 +ENSG00000138231 DBR1 lung pneumocytes Low Supported Q9UK59 51163 +ENSG00000138356 AOX1 bronchus respiratory epithelial cells Low Enhanced Q06278 316 +ENSG00000138356 AOX1 lung macrophages Low Enhanced Q06278 316 +ENSG00000138363 ATIC bronchus respiratory epithelial cells High Supported P31939 471 +ENSG00000138363 ATIC lung macrophages Medium Supported P31939 471 +ENSG00000138376 BARD1 bronchus respiratory epithelial cells Low Enhanced Q99728 580 +ENSG00000138376 BARD1 lung macrophages Medium Enhanced Q99728 580 +ENSG00000138378 STAT4 bronchus respiratory epithelial cells Low Enhanced Q14765 6775 +ENSG00000138378 STAT4 lung macrophages Low Enhanced Q14765 6775 +ENSG00000138385 SSB bronchus respiratory epithelial cells High Supported P05455 6741 +ENSG00000138385 SSB lung macrophages High Supported P05455 6741 +ENSG00000138385 SSB lung pneumocytes High Supported P05455 6741 +ENSG00000138398 PPIG bronchus respiratory epithelial cells High Supported Q13427 9360 +ENSG00000138398 PPIG lung macrophages High Supported Q13427 9360 +ENSG00000138398 PPIG lung pneumocytes High Supported Q13427 9360 +ENSG00000138413 IDH1 bronchus respiratory epithelial cells Low Enhanced O75874 3417 +ENSG00000138413 IDH1 lung macrophages Low Enhanced O75874 3417 +ENSG00000138413 IDH1 lung pneumocytes Low Enhanced O75874 3417 +ENSG00000138448 ITGAV bronchus respiratory epithelial cells Medium Supported P06756 3685 +ENSG00000138495 COX17 bronchus respiratory epithelial cells High Supported Q14061 10063 +ENSG00000138495 COX17 lung macrophages Medium Supported Q14061 10063 +ENSG00000138495 COX17 lung pneumocytes Low Supported Q14061 10063 +ENSG00000138600 SPPL2A bronchus respiratory epithelial cells Medium Enhanced Q8TCT8 84888 +ENSG00000138600 SPPL2A lung macrophages Medium Enhanced Q8TCT8 84888 +ENSG00000138600 SPPL2A lung pneumocytes Low Enhanced Q8TCT8 84888 +ENSG00000138668 HNRNPD bronchus respiratory epithelial cells Medium Supported Q14103 3184 +ENSG00000138668 HNRNPD lung macrophages High Supported Q14103 3184 +ENSG00000138668 HNRNPD lung pneumocytes High Supported Q14103 3184 +ENSG00000138738 PRDM5 bronchus respiratory epithelial cells High Enhanced Q9NQX1 11107 +ENSG00000138738 PRDM5 lung macrophages Medium Enhanced Q9NQX1 11107 +ENSG00000138738 PRDM5 lung pneumocytes Medium Enhanced Q9NQX1 11107 +ENSG00000138757 G3BP2 bronchus respiratory epithelial cells High Enhanced Q9UN86 9908 +ENSG00000138757 G3BP2 lung macrophages High Enhanced Q9UN86 9908 +ENSG00000138757 G3BP2 lung pneumocytes Medium Enhanced Q9UN86 9908 +ENSG00000138760 SCARB2 bronchus respiratory epithelial cells High Supported Q14108 950 +ENSG00000138760 SCARB2 lung macrophages High Supported Q14108 950 +ENSG00000138760 SCARB2 lung pneumocytes Medium Supported Q14108 950 +ENSG00000138768 USO1 bronchus respiratory epithelial cells Medium Supported O60763 8615 +ENSG00000138768 USO1 lung macrophages Medium Supported O60763 8615 +ENSG00000138768 USO1 lung pneumocytes Low Supported O60763 8615 +ENSG00000138771 SHROOM3 bronchus respiratory epithelial cells Medium Enhanced Q8TF72 57619 +ENSG00000138771 SHROOM3 lung macrophages Low Enhanced Q8TF72 57619 +ENSG00000138772 ANXA3 bronchus respiratory epithelial cells Medium Enhanced P12429 306 +ENSG00000138772 ANXA3 lung pneumocytes Medium Enhanced P12429 306 +ENSG00000138777 PPA2 bronchus respiratory epithelial cells Medium Supported Q9H2U2 27068 +ENSG00000138777 PPA2 lung macrophages High Supported Q9H2U2 27068 +ENSG00000138777 PPA2 lung pneumocytes Medium Supported Q9H2U2 27068 +ENSG00000138792 ENPEP lung macrophages Low Enhanced Q07075 2028 +ENSG00000138792 ENPEP lung pneumocytes Low Enhanced Q07075 2028 +ENSG00000138794 CASP6 bronchus respiratory epithelial cells Low Enhanced P55212 839 +ENSG00000138796 HADH lung macrophages High Supported Q16836 3033 +ENSG00000138796 HADH lung pneumocytes Medium Supported Q16836 3033 +ENSG00000138814 PPP3CA bronchus respiratory epithelial cells Medium Enhanced Q08209 5530 +ENSG00000139044 B4GALNT3 bronchus respiratory epithelial cells Medium Enhanced Q6L9W6 283358 +ENSG00000139044 B4GALNT3 lung macrophages Low Enhanced Q6L9W6 283358 +ENSG00000139044 B4GALNT3 lung pneumocytes Low Enhanced Q6L9W6 283358 +ENSG00000139083 ETV6 bronchus respiratory epithelial cells Low Enhanced P41212 2120 +ENSG00000139083 ETV6 lung pneumocytes Low Enhanced P41212 2120 +ENSG00000139116 KIF21A bronchus respiratory epithelial cells High Enhanced Q7Z4S6 55605 +ENSG00000139174 PRICKLE1 bronchus respiratory epithelial cells Low Enhanced Q96MT3 144165 +ENSG00000139178 C1RL bronchus respiratory epithelial cells Medium Supported Q9NZP8 51279 +ENSG00000139180 NDUFA9 bronchus respiratory epithelial cells Medium Enhanced Q16795 4704 +ENSG00000139180 NDUFA9 lung macrophages Low Enhanced Q16795 4704 +ENSG00000139180 NDUFA9 lung pneumocytes Low Enhanced Q16795 4704 +ENSG00000139194 RBP5 bronchus respiratory epithelial cells Medium Enhanced P82980 83758 +ENSG00000139194 RBP5 lung macrophages Medium Enhanced P82980 83758 +ENSG00000139194 RBP5 lung pneumocytes Medium Enhanced P82980 83758 +ENSG00000139197 PEX5 bronchus respiratory epithelial cells High Enhanced P50542 5830 +ENSG00000139197 PEX5 lung macrophages High Enhanced P50542 5830 +ENSG00000139197 PEX5 lung pneumocytes Low Enhanced P50542 5830 +ENSG00000139200 PIANP bronchus respiratory epithelial cells Low Enhanced Q8IYJ0 196500 +ENSG00000139218 SCAF11 bronchus respiratory epithelial cells Medium Enhanced Q99590 9169 +ENSG00000139218 SCAF11 lung macrophages Medium Enhanced Q99590 9169 +ENSG00000139218 SCAF11 lung pneumocytes Medium Enhanced Q99590 9169 +ENSG00000139372 TDG bronchus respiratory epithelial cells High Supported Q13569 6996 +ENSG00000139372 TDG lung macrophages Medium Supported Q13569 6996 +ENSG00000139372 TDG lung pneumocytes Low Supported Q13569 6996 +ENSG00000139405 RITA1 bronchus respiratory epithelial cells High Supported Q96K30 84934 +ENSG00000139405 RITA1 lung macrophages Medium Supported Q96K30 84934 +ENSG00000139405 RITA1 lung pneumocytes Low Supported Q96K30 84934 +ENSG00000139437 TCHP bronchus respiratory epithelial cells Medium Supported Q9BT92 84260 +ENSG00000139437 TCHP lung macrophages Low Supported Q9BT92 84260 +ENSG00000139437 TCHP lung pneumocytes Low Supported Q9BT92 84260 +ENSG00000139579 NABP2 bronchus respiratory epithelial cells Medium Supported Q9BQ15 79035 +ENSG00000139579 NABP2 lung pneumocytes Low Supported Q9BQ15 79035 +ENSG00000139613 SMARCC2 bronchus respiratory epithelial cells High Supported Q8TAQ2 6601 +ENSG00000139613 SMARCC2 lung macrophages High Supported Q8TAQ2 6601 +ENSG00000139613 SMARCC2 lung pneumocytes High Supported Q8TAQ2 6601 +ENSG00000139629 GALNT6 bronchus respiratory epithelial cells Medium Enhanced Q8NCL4 11226 +ENSG00000139629 GALNT6 lung macrophages Low Enhanced Q8NCL4 11226 +ENSG00000139629 GALNT6 lung pneumocytes Low Enhanced Q8NCL4 11226 +ENSG00000139687 RB1 bronchus respiratory epithelial cells Medium Supported P06400 5925 +ENSG00000139687 RB1 lung macrophages Medium Supported P06400 5925 +ENSG00000139687 RB1 lung pneumocytes Medium Supported P06400 5925 +ENSG00000139722 VPS37B bronchus respiratory epithelial cells Medium Enhanced Q9H9H4 79720 +ENSG00000139722 VPS37B lung macrophages Medium Enhanced Q9H9H4 79720 +ENSG00000139725 RHOF bronchus respiratory epithelial cells Low Enhanced Q9HBH0 54509 +ENSG00000139725 RHOF lung macrophages Medium Enhanced Q9HBH0 54509 +ENSG00000139908 TSSK4 lung macrophages Low Enhanced Q6SA08 283629 +ENSG00000139971 C14orf37 bronchus respiratory epithelial cells Medium Enhanced Q86TY3 145407 +ENSG00000139971 C14orf37 lung macrophages Low Enhanced Q86TY3 145407 +ENSG00000140022 STON2 bronchus respiratory epithelial cells Medium Enhanced Q8WXE9 85439 +ENSG00000140022 STON2 lung macrophages Low Enhanced Q8WXE9 85439 +ENSG00000140044 JDP2 bronchus respiratory epithelial cells High Supported Q8WYK2 122953 +ENSG00000140044 JDP2 lung macrophages Low Supported Q8WYK2 122953 +ENSG00000140044 JDP2 lung pneumocytes Medium Supported Q8WYK2 122953 +ENSG00000140057 AK7 bronchus respiratory epithelial cells Medium Enhanced Q96M32 122481 +ENSG00000140057 AK7 lung macrophages Low Enhanced Q96M32 122481 +ENSG00000140263 SORD bronchus respiratory epithelial cells Low Enhanced Q00796 6652 +ENSG00000140265 ZSCAN29 bronchus respiratory epithelial cells High Enhanced Q8IWY8 146050 +ENSG00000140265 ZSCAN29 lung macrophages Medium Enhanced Q8IWY8 146050 +ENSG00000140265 ZSCAN29 lung pneumocytes Medium Enhanced Q8IWY8 146050 +ENSG00000140326 CDAN1 bronchus respiratory epithelial cells Medium Enhanced Q8IWY9 146059 +ENSG00000140326 CDAN1 lung pneumocytes Low Enhanced Q8IWY9 146059 +ENSG00000140350 ANP32A bronchus respiratory epithelial cells High Supported P39687 8125 +ENSG00000140350 ANP32A lung macrophages Medium Supported P39687 8125 +ENSG00000140350 ANP32A lung pneumocytes High Supported P39687 8125 +ENSG00000140368 PSTPIP1 lung macrophages Low Enhanced O43586 9051 +ENSG00000140374 ETFA bronchus respiratory epithelial cells Medium Enhanced P13804 2108 +ENSG00000140374 ETFA lung macrophages Medium Enhanced P13804 2108 +ENSG00000140374 ETFA lung pneumocytes Low Enhanced P13804 2108 +ENSG00000140382 HMG20A lung macrophages High Supported Q9NP66 10363 +ENSG00000140382 HMG20A lung pneumocytes High Supported Q9NP66 10363 +ENSG00000140395 WDR61 bronchus respiratory epithelial cells Medium Enhanced Q9GZS3 80349 +ENSG00000140395 WDR61 lung macrophages Low Enhanced Q9GZS3 80349 +ENSG00000140451 PIF1 bronchus respiratory epithelial cells High Supported Q9H611 80119 +ENSG00000140451 PIF1 lung macrophages Medium Supported Q9H611 80119 +ENSG00000140451 PIF1 lung pneumocytes High Supported Q9H611 80119 +ENSG00000140464 PML bronchus respiratory epithelial cells High Supported P29590 5371 +ENSG00000140464 PML lung macrophages Low Supported P29590 5371 +ENSG00000140464 PML lung pneumocytes Medium Supported P29590 5371 +ENSG00000140538 NTRK3 bronchus respiratory epithelial cells Low Enhanced Q16288 4916 +ENSG00000140538 NTRK3 lung macrophages Low Enhanced Q16288 4916 +ENSG00000140548 ZNF710 bronchus respiratory epithelial cells High Enhanced Q8N1W2 374655 +ENSG00000140548 ZNF710 lung macrophages Medium Enhanced Q8N1W2 374655 +ENSG00000140548 ZNF710 lung pneumocytes Medium Enhanced Q8N1W2 374655 +ENSG00000140575 IQGAP1 bronchus respiratory epithelial cells Medium Enhanced P46940 8826 +ENSG00000140575 IQGAP1 lung macrophages High Enhanced P46940 8826 +ENSG00000140575 IQGAP1 lung pneumocytes Low Enhanced P46940 8826 +ENSG00000140632 GLYR1 bronchus respiratory epithelial cells High Enhanced Q49A26 84656 +ENSG00000140632 GLYR1 lung macrophages High Enhanced Q49A26 84656 +ENSG00000140632 GLYR1 lung pneumocytes High Enhanced Q49A26 84656 +ENSG00000140678 ITGAX lung macrophages Low Enhanced P20702 3687 +ENSG00000140682 TGFB1I1 bronchus respiratory epithelial cells Low Enhanced O43294 7041 +ENSG00000140682 TGFB1I1 lung pneumocytes Low Enhanced O43294 7041 +ENSG00000140694 PARN bronchus respiratory epithelial cells High Enhanced NA NA +ENSG00000140694 PARN lung macrophages High Enhanced NA NA +ENSG00000140694 PARN lung pneumocytes High Enhanced NA NA +ENSG00000140718 FTO bronchus respiratory epithelial cells Medium Enhanced Q9C0B1 79068 +ENSG00000140718 FTO lung macrophages Low Enhanced Q9C0B1 79068 +ENSG00000140718 FTO lung pneumocytes Medium Enhanced Q9C0B1 79068 +ENSG00000140740 UQCRC2 bronchus respiratory epithelial cells Medium Enhanced H3BUI9 NA +ENSG00000140740 UQCRC2 lung macrophages Medium Enhanced H3BUI9 NA +ENSG00000140740 UQCRC2 lung pneumocytes Low Enhanced H3BUI9 NA +ENSG00000140854 KATNB1 bronchus respiratory epithelial cells Medium Enhanced Q9BVA0 10300 +ENSG00000140854 KATNB1 lung macrophages Medium Enhanced Q9BVA0 10300 +ENSG00000140876 NUDT7 bronchus respiratory epithelial cells Medium Supported P0C024 283927 +ENSG00000140876 NUDT7 lung macrophages Medium Supported P0C024 283927 +ENSG00000140876 NUDT7 lung pneumocytes Low Supported P0C024 283927 +ENSG00000140937 CDH11 bronchus respiratory epithelial cells Low Enhanced P55287 1009 +ENSG00000140937 CDH11 lung pneumocytes Medium Enhanced P55287 1009 +ENSG00000140939 NOL3 lung pneumocytes Medium Enhanced O60936 8996 +ENSG00000140943 MBTPS1 bronchus respiratory epithelial cells Medium Supported Q14703 8720 +ENSG00000140943 MBTPS1 lung macrophages High Supported Q14703 8720 +ENSG00000140968 IRF8 lung macrophages Medium Enhanced Q02556 3394 +ENSG00000140990 NDUFB10 bronchus respiratory epithelial cells Medium Enhanced O96000 4716 +ENSG00000140990 NDUFB10 lung macrophages Medium Enhanced O96000 4716 +ENSG00000140990 NDUFB10 lung pneumocytes Low Enhanced O96000 4716 +ENSG00000140992 PDPK1 bronchus respiratory epithelial cells Medium Supported O15530 5170 +ENSG00000140992 PDPK1 lung macrophages Low Supported O15530 5170 +ENSG00000140992 PDPK1 lung pneumocytes Low Supported O15530 5170 +ENSG00000141002 TCF25 bronchus respiratory epithelial cells High Enhanced Q9BQ70 22980 +ENSG00000141002 TCF25 lung macrophages Medium Enhanced Q9BQ70 22980 +ENSG00000141002 TCF25 lung pneumocytes Medium Enhanced Q9BQ70 22980 +ENSG00000141012 GALNS bronchus respiratory epithelial cells High Enhanced P34059 2588 +ENSG00000141012 GALNS lung macrophages Medium Enhanced P34059 2588 +ENSG00000141012 GALNS lung pneumocytes Medium Enhanced P34059 2588 +ENSG00000141027 NCOR1 bronchus respiratory epithelial cells High Enhanced O75376 9611 +ENSG00000141027 NCOR1 lung macrophages Medium Enhanced O75376 9611 +ENSG00000141027 NCOR1 lung pneumocytes Medium Enhanced O75376 9611 +ENSG00000141252 VPS53 bronchus respiratory epithelial cells Medium Enhanced E7EVT8 NA +ENSG00000141252 VPS53 lung macrophages Medium Enhanced E7EVT8 NA +ENSG00000141252 VPS53 lung pneumocytes Medium Enhanced E7EVT8 NA +ENSG00000141294 LRRC46 bronchus respiratory epithelial cells Medium Enhanced Q96FV0 90506 +ENSG00000141295 SCRN2 lung macrophages Low Enhanced Q96FV2 90507 +ENSG00000141337 ARSG lung macrophages Low Enhanced Q96EG1 22901 +ENSG00000141338 ABCA8 lung macrophages Low Enhanced O94911 10351 +ENSG00000141338 ABCA8 lung pneumocytes Low Enhanced O94911 10351 +ENSG00000141378 PTRH2 bronchus respiratory epithelial cells High Supported Q9Y3E5 51651 +ENSG00000141378 PTRH2 lung macrophages High Supported Q9Y3E5 51651 +ENSG00000141378 PTRH2 lung pneumocytes Medium Supported Q9Y3E5 51651 +ENSG00000141380 SS18 bronchus respiratory epithelial cells Medium Supported Q15532 6760 +ENSG00000141380 SS18 lung macrophages Low Supported Q15532 6760 +ENSG00000141380 SS18 lung pneumocytes Medium Supported Q15532 6760 +ENSG00000141385 AFG3L2 bronchus respiratory epithelial cells Medium Enhanced Q9Y4W6 10939 +ENSG00000141385 AFG3L2 lung macrophages High Enhanced Q9Y4W6 10939 +ENSG00000141385 AFG3L2 lung pneumocytes Low Enhanced Q9Y4W6 10939 +ENSG00000141404 GNAL bronchus respiratory epithelial cells Medium Supported P38405 2774 +ENSG00000141404 GNAL lung macrophages Medium Supported P38405 2774 +ENSG00000141404 GNAL lung pneumocytes Low Supported P38405 2774 +ENSG00000141425 RPRD1A bronchus respiratory epithelial cells High Supported Q96P16 55197 +ENSG00000141425 RPRD1A lung macrophages Low Supported Q96P16 55197 +ENSG00000141425 RPRD1A lung pneumocytes Low Supported Q96P16 55197 +ENSG00000141447 OSBPL1A bronchus respiratory epithelial cells Medium Supported Q9BXW6 114876 +ENSG00000141447 OSBPL1A lung macrophages Medium Supported Q9BXW6 114876 +ENSG00000141447 OSBPL1A lung pneumocytes Medium Supported Q9BXW6 114876 +ENSG00000141456 PELP1 bronchus respiratory epithelial cells High Supported Q8IZL8 27043 +ENSG00000141456 PELP1 lung macrophages High Supported Q8IZL8 27043 +ENSG00000141456 PELP1 lung pneumocytes High Supported Q8IZL8 27043 +ENSG00000141469 SLC14A1 bronchus respiratory epithelial cells Low Supported Q13336 6563 +ENSG00000141469 SLC14A1 lung macrophages Low Supported Q13336 6563 +ENSG00000141469 SLC14A1 lung pneumocytes Low Supported Q13336 6563 +ENSG00000141499 WRAP53 bronchus respiratory epithelial cells Medium Enhanced Q9BUR4 55135 +ENSG00000141499 WRAP53 lung macrophages Medium Enhanced Q9BUR4 55135 +ENSG00000141499 WRAP53 lung pneumocytes Low Enhanced Q9BUR4 55135 +ENSG00000141519 CCDC40 bronchus respiratory epithelial cells Medium Enhanced Q4G0X9 55036 +ENSG00000141543 EIF4A3 bronchus respiratory epithelial cells High Enhanced P38919 9775 +ENSG00000141543 EIF4A3 lung macrophages High Enhanced P38919 9775 +ENSG00000141543 EIF4A3 lung pneumocytes Medium Enhanced P38919 9775 +ENSG00000141570 CBX8 bronchus respiratory epithelial cells High Enhanced Q9HC52 57332 +ENSG00000141570 CBX8 lung macrophages Low Enhanced Q9HC52 57332 +ENSG00000141579 ZNF750 lung macrophages Low Enhanced Q32MQ0 79755 +ENSG00000141579 ZNF750 lung pneumocytes Low Enhanced Q32MQ0 79755 +ENSG00000141736 ERBB2 bronchus respiratory epithelial cells Medium Enhanced P04626 2064 +ENSG00000141736 ERBB2 lung pneumocytes Low Enhanced P04626 2064 +ENSG00000141753 IGFBP4 bronchus respiratory epithelial cells Low Supported P22692 3487 +ENSG00000141756 FKBP10 bronchus respiratory epithelial cells Medium Enhanced Q96AY3 60681 +ENSG00000141756 FKBP10 lung macrophages Low Enhanced Q96AY3 60681 +ENSG00000141867 BRD4 bronchus respiratory epithelial cells High Enhanced O60885 23476 +ENSG00000141867 BRD4 lung macrophages High Enhanced O60885 23476 +ENSG00000141867 BRD4 lung pneumocytes High Enhanced O60885 23476 +ENSG00000141905 NFIC bronchus respiratory epithelial cells High Supported P08651 4782 +ENSG00000141905 NFIC lung pneumocytes High Supported P08651 4782 +ENSG00000141968 VAV1 lung macrophages Low Enhanced P15498 7409 +ENSG00000142039 CCDC97 bronchus respiratory epithelial cells High Enhanced Q96F63 90324 +ENSG00000142039 CCDC97 lung macrophages Medium Enhanced Q96F63 90324 +ENSG00000142039 CCDC97 lung pneumocytes Low Enhanced Q96F63 90324 +ENSG00000142168 SOD1 bronchus respiratory epithelial cells Medium Enhanced P00441 6647 +ENSG00000142168 SOD1 lung macrophages Low Enhanced P00441 6647 +ENSG00000142168 SOD1 lung pneumocytes Low Enhanced P00441 6647 +ENSG00000142173 COL6A2 bronchus respiratory epithelial cells Medium Enhanced P12110 1292 +ENSG00000142173 COL6A2 lung pneumocytes Low Enhanced P12110 1292 +ENSG00000142185 TRPM2 bronchus respiratory epithelial cells Low Enhanced O94759 7226 +ENSG00000142207 URB1 bronchus respiratory epithelial cells High Supported O60287 9875 +ENSG00000142207 URB1 lung macrophages Low Supported O60287 9875 +ENSG00000142207 URB1 lung pneumocytes Medium Supported O60287 9875 +ENSG00000142208 AKT1 bronchus respiratory epithelial cells High Enhanced P31749 207 +ENSG00000142208 AKT1 lung macrophages Medium Enhanced P31749 207 +ENSG00000142208 AKT1 lung pneumocytes High Enhanced P31749 207 +ENSG00000142230 SAE1 bronchus respiratory epithelial cells Medium Enhanced Q9UBE0 10055 +ENSG00000142230 SAE1 lung macrophages Low Enhanced Q9UBE0 10055 +ENSG00000142409 ZNF787 bronchus respiratory epithelial cells Medium Supported Q6DD87 126208 +ENSG00000142409 ZNF787 lung macrophages Low Supported Q6DD87 126208 +ENSG00000142409 ZNF787 lung pneumocytes Low Supported Q6DD87 126208 +ENSG00000142453 CARM1 bronchus respiratory epithelial cells Medium Supported Q86X55 10498 +ENSG00000142453 CARM1 lung macrophages Medium Supported Q86X55 10498 +ENSG00000142453 CARM1 lung pneumocytes Low Supported Q86X55 10498 +ENSG00000142494 SLC47A1 bronchus respiratory epithelial cells Low Enhanced Q96FL8 55244 +ENSG00000142494 SLC47A1 lung macrophages Low Enhanced Q96FL8 55244 +ENSG00000142507 PSMB6 bronchus respiratory epithelial cells Medium Supported P28072 5694 +ENSG00000142507 PSMB6 lung macrophages High Supported P28072 5694 +ENSG00000142507 PSMB6 lung pneumocytes Low Supported P28072 5694 +ENSG00000142583 SLC2A5 lung macrophages Low Enhanced P22732 6518 +ENSG00000142609 CFAP74 bronchus respiratory epithelial cells Medium Enhanced Q9C0B2 85452 +ENSG00000142621 FHAD1 bronchus respiratory epithelial cells High Enhanced B1AJZ9 114827 +ENSG00000142634 EFHD2 lung macrophages Medium Enhanced Q96C19 79180 +ENSG00000142634 EFHD2 lung pneumocytes Medium Enhanced Q96C19 79180 +ENSG00000142655 PEX14 bronchus respiratory epithelial cells High Supported O75381 5195 +ENSG00000142655 PEX14 lung macrophages Low Supported O75381 5195 +ENSG00000142655 PEX14 lung pneumocytes High Supported O75381 5195 +ENSG00000142657 PGD bronchus respiratory epithelial cells Medium Enhanced P52209 5226 +ENSG00000142657 PGD lung macrophages Medium Enhanced P52209 5226 +ENSG00000142684 ZNF593 bronchus respiratory epithelial cells High Supported O00488 51042 +ENSG00000142684 ZNF593 lung macrophages High Supported O00488 51042 +ENSG00000142684 ZNF593 lung pneumocytes High Supported O00488 51042 +ENSG00000142765 SYTL1 bronchus respiratory epithelial cells Medium Enhanced Q8IYJ3 84958 +ENSG00000142765 SYTL1 lung macrophages Low Enhanced Q8IYJ3 84958 +ENSG00000142794 NBPF3 bronchus respiratory epithelial cells Low Supported Q9H094 84224 +ENSG00000142864 SERBP1 bronchus respiratory epithelial cells High Enhanced Q8NC51 26135 +ENSG00000142864 SERBP1 lung macrophages Medium Enhanced Q8NC51 26135 +ENSG00000143036 SLC44A3 bronchus respiratory epithelial cells Medium Enhanced Q8N4M1 126969 +ENSG00000143153 ATP1B1 bronchus respiratory epithelial cells High Enhanced P05026 481 +ENSG00000143153 ATP1B1 lung macrophages Medium Enhanced P05026 481 +ENSG00000143153 ATP1B1 lung pneumocytes Low Enhanced P05026 481 +ENSG00000143190 POU2F1 lung macrophages Medium Supported P14859 5451 +ENSG00000143222 UFC1 bronchus respiratory epithelial cells Medium Enhanced Q9Y3C8 51506 +ENSG00000143222 UFC1 lung pneumocytes Medium Enhanced Q9Y3C8 51506 +ENSG00000143226 FCGR2A lung macrophages Medium Enhanced P12318 2212 +ENSG00000143294 PRCC bronchus respiratory epithelial cells High Supported Q92733 5546 +ENSG00000143294 PRCC lung macrophages Low Supported Q92733 5546 +ENSG00000143318 CASQ1 bronchus respiratory epithelial cells Low Enhanced P31415 844 +ENSG00000143318 CASQ1 lung macrophages Low Enhanced P31415 844 +ENSG00000143321 HDGF bronchus respiratory epithelial cells High Enhanced P51858 3068 +ENSG00000143321 HDGF lung macrophages Low Enhanced P51858 3068 +ENSG00000143321 HDGF lung pneumocytes High Enhanced P51858 3068 +ENSG00000143324 XPR1 bronchus respiratory epithelial cells High Enhanced Q9UBH6 9213 +ENSG00000143324 XPR1 lung macrophages Medium Enhanced Q9UBH6 9213 +ENSG00000143324 XPR1 lung pneumocytes Medium Enhanced Q9UBH6 9213 +ENSG00000143337 TOR1AIP1 lung macrophages Medium Enhanced Q5JTV8 26092 +ENSG00000143337 TOR1AIP1 lung pneumocytes Medium Enhanced Q5JTV8 26092 +ENSG00000143369 ECM1 bronchus respiratory epithelial cells Low Enhanced Q16610 1893 +ENSG00000143375 CGN bronchus respiratory epithelial cells High Enhanced Q9P2M7 57530 +ENSG00000143375 CGN lung pneumocytes Low Enhanced Q9P2M7 57530 +ENSG00000143390 RFX5 bronchus respiratory epithelial cells High Supported P48382 5993 +ENSG00000143390 RFX5 lung macrophages Medium Supported P48382 5993 +ENSG00000143390 RFX5 lung pneumocytes High Supported P48382 5993 +ENSG00000143401 ANP32E bronchus respiratory epithelial cells High Supported Q9BTT0 81611 +ENSG00000143401 ANP32E lung macrophages Medium Supported Q9BTT0 81611 +ENSG00000143401 ANP32E lung pneumocytes High Supported Q9BTT0 81611 +ENSG00000143412 ANXA9 bronchus respiratory epithelial cells Medium Enhanced O76027 8416 +ENSG00000143412 ANXA9 lung macrophages Medium Enhanced O76027 8416 +ENSG00000143412 ANXA9 lung pneumocytes Low Enhanced O76027 8416 +ENSG00000143416 SELENBP1 bronchus respiratory epithelial cells High Enhanced Q13228 8991 +ENSG00000143416 SELENBP1 lung macrophages Low Enhanced Q13228 8991 +ENSG00000143416 SELENBP1 lung pneumocytes Medium Enhanced Q13228 8991 +ENSG00000143437 ARNT bronchus respiratory epithelial cells Low Enhanced P27540 405 +ENSG00000143437 ARNT lung macrophages Medium Enhanced P27540 405 +ENSG00000143437 ARNT lung pneumocytes Medium Enhanced P27540 405 +ENSG00000143442 POGZ bronchus respiratory epithelial cells High Enhanced Q7Z3K3 23126 +ENSG00000143442 POGZ lung macrophages High Enhanced Q7Z3K3 23126 +ENSG00000143442 POGZ lung pneumocytes Medium Enhanced Q7Z3K3 23126 +ENSG00000143514 TP53BP2 bronchus respiratory epithelial cells High Supported Q13625 7159 +ENSG00000143514 TP53BP2 lung macrophages Medium Supported Q13625 7159 +ENSG00000143514 TP53BP2 lung pneumocytes Medium Supported Q13625 7159 +ENSG00000143578 CREB3L4 bronchus respiratory epithelial cells Medium Enhanced Q8TEY5 148327 +ENSG00000143578 CREB3L4 lung macrophages Medium Enhanced Q8TEY5 148327 +ENSG00000143578 CREB3L4 lung pneumocytes Low Enhanced Q8TEY5 148327 +ENSG00000143621 ILF2 bronchus respiratory epithelial cells High Supported Q12905 3608 +ENSG00000143621 ILF2 lung macrophages High Supported Q12905 3608 +ENSG00000143621 ILF2 lung pneumocytes High Supported Q12905 3608 +ENSG00000143633 C1orf131 bronchus respiratory epithelial cells Medium Enhanced Q8NDD1 128061 +ENSG00000143633 C1orf131 lung macrophages Medium Enhanced Q8NDD1 128061 +ENSG00000143633 C1orf131 lung pneumocytes Low Enhanced Q8NDD1 128061 +ENSG00000143641 GALNT2 bronchus respiratory epithelial cells Medium Supported Q10471 2590 +ENSG00000143641 GALNT2 lung macrophages Medium Supported Q10471 2590 +ENSG00000143740 SNAP47 bronchus respiratory epithelial cells High Enhanced Q5SQN1 116841 +ENSG00000143740 SNAP47 lung macrophages Low Enhanced Q5SQN1 116841 +ENSG00000143740 SNAP47 lung pneumocytes Medium Enhanced Q5SQN1 116841 +ENSG00000143748 NVL bronchus respiratory epithelial cells Low Enhanced O15381 4931 +ENSG00000143799 PARP1 bronchus respiratory epithelial cells High Supported P09874 142 +ENSG00000143799 PARP1 lung pneumocytes Medium Supported P09874 142 +ENSG00000143819 EPHX1 bronchus respiratory epithelial cells Low Enhanced P07099 2052 +ENSG00000143819 EPHX1 lung macrophages Low Enhanced P07099 2052 +ENSG00000143819 EPHX1 lung pneumocytes Low Enhanced P07099 2052 +ENSG00000143845 ETNK2 bronchus respiratory epithelial cells Low Enhanced Q9NVF9 55224 +ENSG00000143845 ETNK2 lung macrophages Low Enhanced Q9NVF9 55224 +ENSG00000143870 PDIA6 bronchus respiratory epithelial cells Medium Enhanced Q15084 10130 +ENSG00000143870 PDIA6 lung macrophages Medium Enhanced Q15084 10130 +ENSG00000143870 PDIA6 lung pneumocytes Low Enhanced Q15084 10130 +ENSG00000143891 GALM bronchus respiratory epithelial cells Low Enhanced Q96C23 130589 +ENSG00000143924 EML4 bronchus respiratory epithelial cells Medium Enhanced Q9HC35 27436 +ENSG00000143924 EML4 lung macrophages High Enhanced Q9HC35 27436 +ENSG00000143947 RPS27A bronchus respiratory epithelial cells High Supported P62979 6233 +ENSG00000143947 RPS27A lung macrophages Medium Supported P62979 6233 +ENSG00000143947 RPS27A lung pneumocytes Medium Supported P62979 6233 +ENSG00000143977 SNRPG bronchus respiratory epithelial cells High Enhanced P62308 6637 +ENSG00000143977 SNRPG lung macrophages Low Enhanced P62308 6637 +ENSG00000143977 SNRPG lung pneumocytes Medium Enhanced P62308 6637 +ENSG00000144366 GULP1 bronchus respiratory epithelial cells Medium Enhanced Q9UBP9 51454 +ENSG00000144381 HSPD1 bronchus respiratory epithelial cells High Supported P10809 3329 +ENSG00000144381 HSPD1 lung macrophages Low Supported P10809 3329 +ENSG00000144597 EAF1 lung macrophages High Enhanced Q96JC9 85403 +ENSG00000144597 EAF1 lung pneumocytes High Enhanced Q96JC9 85403 +ENSG00000144648 ACKR2 bronchus respiratory epithelial cells Medium Enhanced O00590 1238 +ENSG00000144648 ACKR2 lung macrophages Low Enhanced O00590 1238 +ENSG00000144674 GOLGA4 bronchus respiratory epithelial cells Medium Supported Q13439 2803 +ENSG00000144674 GOLGA4 lung macrophages Medium Supported Q13439 2803 +ENSG00000144674 GOLGA4 lung pneumocytes Medium Supported Q13439 2803 +ENSG00000144713 RPL32 bronchus respiratory epithelial cells Medium Enhanced P62910 6161 +ENSG00000144713 RPL32 lung macrophages Low Enhanced P62910 6161 +ENSG00000144741 SLC25A26 bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000144741 SLC25A26 lung macrophages Medium Enhanced NA NA +ENSG00000144741 SLC25A26 lung pneumocytes Low Enhanced NA NA +ENSG00000144744 UBA3 bronchus respiratory epithelial cells Medium Enhanced Q8TBC4 9039 +ENSG00000144744 UBA3 lung macrophages Medium Enhanced Q8TBC4 9039 +ENSG00000144744 UBA3 lung pneumocytes Medium Enhanced Q8TBC4 9039 +ENSG00000144746 ARL6IP5 bronchus respiratory epithelial cells Medium Supported O75915 10550 +ENSG00000144746 ARL6IP5 lung macrophages Medium Supported O75915 10550 +ENSG00000144746 ARL6IP5 lung pneumocytes Medium Supported O75915 10550 +ENSG00000144802 NFKBIZ lung macrophages Low Enhanced Q9BYH8 64332 +ENSG00000144827 ABHD10 bronchus respiratory epithelial cells High Supported Q9NUJ1 55347 +ENSG00000144827 ABHD10 lung macrophages High Supported Q9NUJ1 55347 +ENSG00000144827 ABHD10 lung pneumocytes High Supported Q9NUJ1 55347 +ENSG00000144848 ATG3 bronchus respiratory epithelial cells Medium Enhanced Q9NT62 64422 +ENSG00000144848 ATG3 lung macrophages Medium Enhanced Q9NT62 64422 +ENSG00000144848 ATG3 lung pneumocytes Medium Enhanced Q9NT62 64422 +ENSG00000144908 ALDH1L1 bronchus respiratory epithelial cells Low Enhanced O75891 10840 +ENSG00000144908 ALDH1L1 lung macrophages Low Enhanced O75891 10840 +ENSG00000144935 TRPC1 bronchus respiratory epithelial cells Medium Supported P48995 7220 +ENSG00000144935 TRPC1 lung macrophages Medium Supported P48995 7220 +ENSG00000144935 TRPC1 lung pneumocytes Medium Supported P48995 7220 +ENSG00000144959 NCEH1 bronchus respiratory epithelial cells Low Supported Q6PIU2 57552 +ENSG00000144959 NCEH1 lung macrophages High Supported Q6PIU2 57552 +ENSG00000144959 NCEH1 lung pneumocytes Medium Supported Q6PIU2 57552 +ENSG00000145012 LPP bronchus respiratory epithelial cells Medium Enhanced Q93052 4026 +ENSG00000145020 AMT bronchus respiratory epithelial cells High Supported P48728 275 +ENSG00000145020 AMT lung macrophages High Supported P48728 275 +ENSG00000145020 AMT lung pneumocytes High Supported P48728 275 +ENSG00000145075 CCDC39 bronchus respiratory epithelial cells High Enhanced Q9UFE4 339829 +ENSG00000145194 ECE2 bronchus respiratory epithelial cells Low Enhanced P0DPD6 110599583; 9718 +ENSG00000145194 ECE2 lung macrophages Low Enhanced P0DPD6 110599583; 9718 +ENSG00000145198 VWA5B2 bronchus respiratory epithelial cells Medium Enhanced Q8N398 90113 +ENSG00000145198 VWA5B2 lung macrophages Low Enhanced Q8N398 90113 +ENSG00000145216 FIP1L1 bronchus respiratory epithelial cells Medium Enhanced Q6UN15 81608 +ENSG00000145216 FIP1L1 lung macrophages Medium Enhanced Q6UN15 81608 +ENSG00000145216 FIP1L1 lung pneumocytes Low Enhanced Q6UN15 81608 +ENSG00000145247 OCIAD2 bronchus respiratory epithelial cells Medium Enhanced Q56VL3 132299 +ENSG00000145247 OCIAD2 lung pneumocytes Low Enhanced Q56VL3 132299 +ENSG00000145283 SLC10A6 bronchus respiratory epithelial cells Medium Enhanced Q3KNW5 345274 +ENSG00000145287 PLAC8 lung macrophages High Supported Q9NZF1 51316 +ENSG00000145287 PLAC8 lung pneumocytes Low Supported Q9NZF1 51316 +ENSG00000145293 ENOPH1 bronchus respiratory epithelial cells Medium Enhanced Q9UHY7 58478 +ENSG00000145293 ENOPH1 lung macrophages Medium Enhanced Q9UHY7 58478 +ENSG00000145321 GC bronchus respiratory epithelial cells Low Supported P02774 2638 +ENSG00000145321 GC lung macrophages Low Supported P02774 2638 +ENSG00000145321 GC lung pneumocytes Low Supported P02774 2638 +ENSG00000145362 ANK2 lung pneumocytes Low Enhanced Q01484 287 +ENSG00000145386 CCNA2 bronchus respiratory epithelial cells Low Enhanced P20248 890 +ENSG00000145388 METTL14 bronchus respiratory epithelial cells Medium Supported Q9HCE5 57721 +ENSG00000145388 METTL14 lung pneumocytes Low Supported Q9HCE5 57721 +ENSG00000145439 CBR4 bronchus respiratory epithelial cells Medium Supported Q8N4T8 84869 +ENSG00000145439 CBR4 lung macrophages Medium Supported Q8N4T8 84869 +ENSG00000145439 CBR4 lung pneumocytes Medium Supported Q8N4T8 84869 +ENSG00000145491 ROPN1L bronchus respiratory epithelial cells High Enhanced Q96C74 83853 +ENSG00000145494 NDUFS6 bronchus respiratory epithelial cells High Supported O75380 4726 +ENSG00000145494 NDUFS6 lung macrophages Medium Supported O75380 4726 +ENSG00000145494 NDUFS6 lung pneumocytes Medium Supported O75380 4726 +ENSG00000145555 MYO10 bronchus respiratory epithelial cells Medium Enhanced Q9HD67 4651 +ENSG00000145555 MYO10 lung macrophages Low Enhanced Q9HD67 4651 +ENSG00000145555 MYO10 lung pneumocytes Low Enhanced Q9HD67 4651 +ENSG00000145715 RASA1 bronchus respiratory epithelial cells Low Enhanced P20936 5921 +ENSG00000145730 PAM bronchus respiratory epithelial cells Medium Enhanced P19021 5066 +ENSG00000145817 YIPF5 bronchus respiratory epithelial cells High Enhanced Q969M3 81555 +ENSG00000145817 YIPF5 lung macrophages High Enhanced Q969M3 81555 +ENSG00000145819 ARHGAP26 lung macrophages Medium Enhanced Q9UNA1 23092 +ENSG00000145833 DDX46 bronchus respiratory epithelial cells High Supported Q7L014 9879 +ENSG00000145833 DDX46 lung macrophages High Supported Q7L014 9879 +ENSG00000145833 DDX46 lung pneumocytes Medium Supported Q7L014 9879 +ENSG00000145879 SPINK7 lung macrophages Low Enhanced P58062 84651 +ENSG00000145907 G3BP1 bronchus respiratory epithelial cells Medium Supported Q13283 10146 +ENSG00000145907 G3BP1 lung macrophages Medium Supported Q13283 10146 +ENSG00000145907 G3BP1 lung pneumocytes Medium Supported Q13283 10146 +ENSG00000145912 NHP2 bronchus respiratory epithelial cells Medium Enhanced Q9NX24 55651 +ENSG00000145912 NHP2 lung pneumocytes Low Enhanced Q9NX24 55651 +ENSG00000146038 DCDC2 bronchus respiratory epithelial cells Medium Enhanced Q9UHG0 51473 +ENSG00000146085 MUT bronchus respiratory epithelial cells Medium Enhanced P22033 4594 +ENSG00000146085 MUT lung macrophages Medium Enhanced P22033 4594 +ENSG00000146085 MUT lung pneumocytes Medium Enhanced P22033 4594 +ENSG00000146094 DOK3 lung macrophages Medium Enhanced Q7L591 79930 +ENSG00000146112 PPP1R18 lung macrophages Low Enhanced NA NA +ENSG00000146232 NFKBIE bronchus respiratory epithelial cells High Supported O00221 4794 +ENSG00000146232 NFKBIE lung macrophages High Supported O00221 4794 +ENSG00000146232 NFKBIE lung pneumocytes Medium Supported O00221 4794 +ENSG00000146242 TPBG bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000146242 TPBG lung macrophages Low Enhanced NA NA +ENSG00000146242 TPBG lung pneumocytes Medium Enhanced NA NA +ENSG00000146386 ABRACL bronchus respiratory epithelial cells Medium Enhanced Q9P1F3 58527 +ENSG00000146386 ABRACL lung macrophages Medium Enhanced Q9P1F3 58527 +ENSG00000146457 WTAP bronchus respiratory epithelial cells High Supported Q15007 9589 +ENSG00000146457 WTAP lung macrophages Medium Supported Q15007 9589 +ENSG00000146457 WTAP lung pneumocytes Medium Supported Q15007 9589 +ENSG00000146469 VIP bronchus respiratory epithelial cells Medium Supported P01282 7432 +ENSG00000146469 VIP lung macrophages Low Supported P01282 7432 +ENSG00000146469 VIP lung pneumocytes Low Supported P01282 7432 +ENSG00000146701 MDH2 bronchus respiratory epithelial cells High Enhanced P40926 4191 +ENSG00000146701 MDH2 lung macrophages High Enhanced P40926 4191 +ENSG00000146701 MDH2 lung pneumocytes High Enhanced P40926 4191 +ENSG00000146729 GBAS bronchus respiratory epithelial cells High Enhanced O75323 2631 +ENSG00000146729 GBAS lung macrophages Medium Enhanced O75323 2631 +ENSG00000146729 GBAS lung pneumocytes Low Enhanced O75323 2631 +ENSG00000146731 CCT6A bronchus respiratory epithelial cells High Supported P40227 908 +ENSG00000146731 CCT6A lung macrophages High Supported P40227 908 +ENSG00000146731 CCT6A lung pneumocytes High Supported P40227 908 +ENSG00000146830 GIGYF1 bronchus respiratory epithelial cells Medium Enhanced O75420 64599 +ENSG00000146830 GIGYF1 lung macrophages High Enhanced O75420 64599 +ENSG00000146830 GIGYF1 lung pneumocytes Low Enhanced O75420 64599 +ENSG00000146834 MEPCE bronchus respiratory epithelial cells Medium Supported Q7L2J0 56257 +ENSG00000146834 MEPCE lung macrophages Medium Supported Q7L2J0 56257 +ENSG00000146834 MEPCE lung pneumocytes Medium Supported Q7L2J0 56257 +ENSG00000147010 SH3KBP1 lung macrophages Low Enhanced Q96B97 30011 +ENSG00000147044 CASK bronchus respiratory epithelial cells Medium Enhanced O14936 8573 +ENSG00000147044 CASK lung macrophages Medium Enhanced O14936 8573 +ENSG00000147044 CASK lung pneumocytes Medium Enhanced O14936 8573 +ENSG00000147050 KDM6A bronchus respiratory epithelial cells Low Enhanced O15550 7403 +ENSG00000147050 KDM6A lung macrophages Medium Enhanced O15550 7403 +ENSG00000147065 MSN lung macrophages Medium Enhanced P26038 4478 +ENSG00000147065 MSN lung pneumocytes Medium Enhanced P26038 4478 +ENSG00000147099 HDAC8 lung macrophages Low Supported Q9BY41 55869 +ENSG00000147099 HDAC8 lung pneumocytes Medium Supported Q9BY41 55869 +ENSG00000147123 NDUFB11 bronchus respiratory epithelial cells High Supported Q9NX14 54539 +ENSG00000147123 NDUFB11 lung macrophages Medium Supported Q9NX14 54539 +ENSG00000147123 NDUFB11 lung pneumocytes Medium Supported Q9NX14 54539 +ENSG00000147124 ZNF41 bronchus respiratory epithelial cells Medium Enhanced P51814 7592 +ENSG00000147124 ZNF41 lung macrophages Medium Enhanced P51814 7592 +ENSG00000147124 ZNF41 lung pneumocytes Medium Enhanced P51814 7592 +ENSG00000147133 TAF1 bronchus respiratory epithelial cells High Supported P21675 6872 +ENSG00000147133 TAF1 lung macrophages Medium Supported P21675 6872 +ENSG00000147133 TAF1 lung pneumocytes High Supported P21675 6872 +ENSG00000147140 NONO bronchus respiratory epithelial cells High Enhanced Q15233 4841 +ENSG00000147140 NONO lung macrophages Medium Enhanced Q15233 4841 +ENSG00000147140 NONO lung pneumocytes High Enhanced Q15233 4841 +ENSG00000147180 ZNF711 bronchus respiratory epithelial cells Medium Enhanced Q9Y462 7552 +ENSG00000147180 ZNF711 lung macrophages Medium Enhanced Q9Y462 7552 +ENSG00000147180 ZNF711 lung pneumocytes Medium Enhanced Q9Y462 7552 +ENSG00000147202 DIAPH2 bronchus respiratory epithelial cells Low Enhanced O60879 1730 +ENSG00000147202 DIAPH2 lung macrophages Low Enhanced O60879 1730 +ENSG00000147202 DIAPH2 lung pneumocytes Low Enhanced O60879 1730 +ENSG00000147274 RBMX bronchus respiratory epithelial cells High Supported P38159 27316 +ENSG00000147274 RBMX lung macrophages Medium Supported P38159 27316 +ENSG00000147274 RBMX lung pneumocytes High Supported P38159 27316 +ENSG00000147316 MCPH1 bronchus respiratory epithelial cells High Supported Q8NEM0 79648 +ENSG00000147316 MCPH1 lung macrophages Medium Supported Q8NEM0 79648 +ENSG00000147316 MCPH1 lung pneumocytes Medium Supported Q8NEM0 79648 +ENSG00000147383 NSDHL bronchus respiratory epithelial cells Medium Enhanced Q15738 50814 +ENSG00000147383 NSDHL lung macrophages Low Enhanced Q15738 50814 +ENSG00000147383 NSDHL lung pneumocytes Low Enhanced Q15738 50814 +ENSG00000147403 RPL10 bronchus respiratory epithelial cells High Enhanced P27635 6134 +ENSG00000147403 RPL10 lung macrophages High Enhanced P27635 6134 +ENSG00000147403 RPL10 lung pneumocytes High Enhanced P27635 6134 +ENSG00000147416 ATP6V1B2 bronchus respiratory epithelial cells Low Enhanced P21281 526 +ENSG00000147416 ATP6V1B2 lung macrophages High Enhanced P21281 526 +ENSG00000147416 ATP6V1B2 lung pneumocytes Medium Enhanced P21281 526 +ENSG00000147421 HMBOX1 bronchus respiratory epithelial cells Low Enhanced Q6NT76 79618 +ENSG00000147421 HMBOX1 lung pneumocytes Low Enhanced Q6NT76 79618 +ENSG00000147437 GNRH1 bronchus respiratory epithelial cells Low Supported P01148 2796 +ENSG00000147437 GNRH1 lung macrophages Low Supported P01148 2796 +ENSG00000147443 DOK2 lung macrophages High Enhanced O60496 9046 +ENSG00000147475 ERLIN2 bronchus respiratory epithelial cells High Enhanced O94905 11160 +ENSG00000147475 ERLIN2 lung macrophages Medium Enhanced O94905 11160 +ENSG00000147475 ERLIN2 lung pneumocytes Low Enhanced O94905 11160 +ENSG00000147649 MTDH bronchus respiratory epithelial cells High Supported Q86UE4 92140 +ENSG00000147649 MTDH lung macrophages Medium Supported Q86UE4 92140 +ENSG00000147649 MTDH lung pneumocytes Medium Supported Q86UE4 92140 +ENSG00000147654 EBAG9 bronchus respiratory epithelial cells Medium Enhanced O00559 9166 +ENSG00000147654 EBAG9 lung macrophages Medium Enhanced O00559 9166 +ENSG00000147654 EBAG9 lung pneumocytes Medium Enhanced O00559 9166 +ENSG00000147697 GSDMC bronchus respiratory epithelial cells Low Supported Q9BYG8 56169 +ENSG00000147697 GSDMC lung macrophages Low Supported Q9BYG8 56169 +ENSG00000147853 AK3 bronchus respiratory epithelial cells Medium Enhanced Q9UIJ7 50808 +ENSG00000147853 AK3 lung macrophages Medium Enhanced Q9UIJ7 50808 +ENSG00000147862 NFIB bronchus respiratory epithelial cells Medium Supported O00712 4781 +ENSG00000147862 NFIB lung pneumocytes High Supported O00712 4781 +ENSG00000147872 PLIN2 bronchus respiratory epithelial cells Low Supported Q99541 123 +ENSG00000148053 NTRK2 lung macrophages Low Enhanced Q16620 4915 +ENSG00000148057 IDNK lung macrophages Medium Enhanced Q5T6J7 414328 +ENSG00000148057 IDNK lung pneumocytes Low Enhanced Q5T6J7 414328 +ENSG00000148090 AUH bronchus respiratory epithelial cells Medium Enhanced Q13825 549 +ENSG00000148090 AUH lung macrophages Medium Enhanced Q13825 549 +ENSG00000148180 GSN bronchus respiratory epithelial cells Medium Supported P06396 2934 +ENSG00000148180 GSN lung macrophages High Supported P06396 2934 +ENSG00000148180 GSN lung pneumocytes Low Supported P06396 2934 +ENSG00000148187 MRRF bronchus respiratory epithelial cells High Enhanced Q96E11 92399 +ENSG00000148187 MRRF lung macrophages Low Enhanced Q96E11 92399 +ENSG00000148187 MRRF lung pneumocytes Medium Enhanced Q96E11 92399 +ENSG00000148308 GTF3C5 bronchus respiratory epithelial cells High Supported Q9Y5Q8 9328 +ENSG00000148308 GTF3C5 lung macrophages Medium Supported Q9Y5Q8 9328 +ENSG00000148308 GTF3C5 lung pneumocytes High Supported Q9Y5Q8 9328 +ENSG00000148346 LCN2 bronchus respiratory epithelial cells Medium Enhanced P80188 3934 +ENSG00000148356 LRSAM1 bronchus respiratory epithelial cells Medium Supported Q6UWE0 90678 +ENSG00000148356 LRSAM1 lung macrophages Medium Supported Q6UWE0 90678 +ENSG00000148356 LRSAM1 lung pneumocytes Medium Supported Q6UWE0 90678 +ENSG00000148357 HMCN2 bronchus respiratory epithelial cells Medium Enhanced Q8NDA2 NA +ENSG00000148358 GPR107 bronchus respiratory epithelial cells Medium Supported Q5VW38 57720 +ENSG00000148358 GPR107 lung macrophages Medium Supported Q5VW38 57720 +ENSG00000148358 GPR107 lung pneumocytes Medium Supported Q5VW38 57720 +ENSG00000148396 SEC16A bronchus respiratory epithelial cells High Supported O15027 9919 +ENSG00000148396 SEC16A lung macrophages Medium Supported O15027 9919 +ENSG00000148400 NOTCH1 bronchus respiratory epithelial cells Medium Supported P46531 4851 +ENSG00000148400 NOTCH1 lung macrophages High Supported P46531 4851 +ENSG00000148400 NOTCH1 lung pneumocytes High Supported P46531 4851 +ENSG00000148450 MSRB2 lung macrophages Medium Enhanced Q9Y3D2 22921 +ENSG00000148483 TMEM236 bronchus respiratory epithelial cells Low Enhanced Q5W0B7 653567 +ENSG00000148584 A1CF bronchus respiratory epithelial cells Low Enhanced Q9NQ94 29974 +ENSG00000148688 RPP30 bronchus respiratory epithelial cells Medium Enhanced P78346 10556 +ENSG00000148688 RPP30 lung macrophages Low Enhanced P78346 10556 +ENSG00000148700 ADD3 bronchus respiratory epithelial cells Medium Supported Q9UEY8 120 +ENSG00000148700 ADD3 lung macrophages Low Supported Q9UEY8 120 +ENSG00000148700 ADD3 lung pneumocytes Low Supported Q9UEY8 120 +ENSG00000148737 TCF7L2 bronchus respiratory epithelial cells High Supported Q9NQB0 6934 +ENSG00000148737 TCF7L2 lung macrophages High Supported Q9NQB0 6934 +ENSG00000148737 TCF7L2 lung pneumocytes High Supported Q9NQB0 6934 +ENSG00000148773 MKI67 bronchus respiratory epithelial cells Low Enhanced P46013 4288 +ENSG00000148773 MKI67 lung macrophages Low Enhanced P46013 4288 +ENSG00000148834 GSTO1 lung macrophages Medium Enhanced P78417 9446 +ENSG00000148835 TAF5 bronchus respiratory epithelial cells High Supported Q15542 6877 +ENSG00000148835 TAF5 lung macrophages High Supported Q15542 6877 +ENSG00000148835 TAF5 lung pneumocytes High Supported Q15542 6877 +ENSG00000148908 RGS10 bronchus respiratory epithelial cells Medium Enhanced O43665 6001 +ENSG00000148908 RGS10 lung macrophages Medium Enhanced O43665 6001 +ENSG00000148908 RGS10 lung pneumocytes Medium Enhanced O43665 6001 +ENSG00000148965 SAA4 bronchus respiratory epithelial cells Low Supported P35542 6291 +ENSG00000148965 SAA4 lung macrophages Low Supported P35542 6291 +ENSG00000148965 SAA4 lung pneumocytes Low Supported P35542 6291 +ENSG00000149021 SCGB1A1 bronchus respiratory epithelial cells High Supported P11684 7356 +ENSG00000149054 ZNF215 lung pneumocytes Low Enhanced Q9UL58 7762 +ENSG00000149091 DGKZ bronchus respiratory epithelial cells Low Supported Q13574 8525 +ENSG00000149091 DGKZ lung pneumocytes Low Supported Q13574 8525 +ENSG00000149115 TNKS1BP1 lung pneumocytes High Enhanced Q9C0C2 85456 +ENSG00000149150 SLC43A1 bronchus respiratory epithelial cells Medium Enhanced O75387 8501 +ENSG00000149150 SLC43A1 lung macrophages Medium Enhanced O75387 8501 +ENSG00000149182 ARFGAP2 bronchus respiratory epithelial cells High Enhanced Q8N6H7 84364 +ENSG00000149182 ARFGAP2 lung macrophages Medium Enhanced Q8N6H7 84364 +ENSG00000149182 ARFGAP2 lung pneumocytes Low Enhanced Q8N6H7 84364 +ENSG00000149187 CELF1 bronchus respiratory epithelial cells High Supported Q92879 10658 +ENSG00000149187 CELF1 lung macrophages Medium Supported Q92879 10658 +ENSG00000149187 CELF1 lung pneumocytes High Supported Q92879 10658 +ENSG00000149218 ENDOD1 bronchus respiratory epithelial cells Medium Enhanced O94919 23052 +ENSG00000149218 ENDOD1 lung macrophages Low Enhanced O94919 23052 +ENSG00000149218 ENDOD1 lung pneumocytes Medium Enhanced O94919 23052 +ENSG00000149257 SERPINH1 bronchus respiratory epithelial cells Low Supported P50454 871 +ENSG00000149257 SERPINH1 lung macrophages Low Supported P50454 871 +ENSG00000149257 SERPINH1 lung pneumocytes High Supported P50454 871 +ENSG00000149269 PAK1 bronchus respiratory epithelial cells Medium Enhanced Q13153 5058 +ENSG00000149269 PAK1 lung macrophages Medium Enhanced Q13153 5058 +ENSG00000149269 PAK1 lung pneumocytes Medium Enhanced Q13153 5058 +ENSG00000149311 ATM bronchus respiratory epithelial cells High Supported Q13315 472 +ENSG00000149311 ATM lung macrophages Medium Supported Q13315 472 +ENSG00000149311 ATM lung pneumocytes High Supported Q13315 472 +ENSG00000149476 TKFC bronchus respiratory epithelial cells Low Enhanced Q3LXA3 26007 +ENSG00000149480 MTA2 bronchus respiratory epithelial cells High Enhanced O94776 9219 +ENSG00000149480 MTA2 lung macrophages High Enhanced O94776 9219 +ENSG00000149480 MTA2 lung pneumocytes High Enhanced O94776 9219 +ENSG00000149532 CPSF7 bronchus respiratory epithelial cells High Supported Q8N684 79869 +ENSG00000149532 CPSF7 lung macrophages Medium Supported Q8N684 79869 +ENSG00000149532 CPSF7 lung pneumocytes High Supported Q8N684 79869 +ENSG00000149636 DSN1 bronchus respiratory epithelial cells Medium Enhanced Q9H410 79980 +ENSG00000149636 DSN1 lung macrophages Medium Enhanced Q9H410 79980 +ENSG00000149636 DSN1 lung pneumocytes Medium Enhanced Q9H410 79980 +ENSG00000149782 PLCB3 bronchus respiratory epithelial cells Low Enhanced Q01970 5331 +ENSG00000149782 PLCB3 lung macrophages Medium Enhanced Q01970 5331 +ENSG00000149806 FAU bronchus respiratory epithelial cells High Supported P62861 NA +ENSG00000149806 FAU lung pneumocytes Low Supported P62861 NA +ENSG00000149923 PPP4C bronchus respiratory epithelial cells Medium Enhanced P60510 5531 +ENSG00000149923 PPP4C lung macrophages High Enhanced P60510 5531 +ENSG00000149923 PPP4C lung pneumocytes Low Enhanced P60510 5531 +ENSG00000149925 ALDOA bronchus respiratory epithelial cells Medium Enhanced P04075 226 +ENSG00000149925 ALDOA lung macrophages Medium Enhanced P04075 226 +ENSG00000149925 ALDOA lung pneumocytes Low Enhanced P04075 226 +ENSG00000150054 MPP7 bronchus respiratory epithelial cells High Enhanced Q5T2T1 143098 +ENSG00000150054 MPP7 lung macrophages Medium Enhanced Q5T2T1 143098 +ENSG00000150054 MPP7 lung pneumocytes Low Enhanced Q5T2T1 143098 +ENSG00000150316 CWC15 bronchus respiratory epithelial cells High Supported Q9P013 51503 +ENSG00000150459 SAP18 bronchus respiratory epithelial cells High Supported O00422 10284 +ENSG00000150459 SAP18 lung macrophages Medium Supported O00422 10284 +ENSG00000150459 SAP18 lung pneumocytes Medium Supported O00422 10284 +ENSG00000150593 PDCD4 bronchus respiratory epithelial cells High Supported Q53EL6 27250 +ENSG00000150593 PDCD4 lung macrophages Medium Supported Q53EL6 27250 +ENSG00000150593 PDCD4 lung pneumocytes Medium Supported Q53EL6 27250 +ENSG00000150637 CD226 lung macrophages High Supported Q15762 10666 +ENSG00000150712 MTMR12 bronchus respiratory epithelial cells High Supported Q9C0I1 54545 +ENSG00000150712 MTMR12 lung macrophages High Supported Q9C0I1 54545 +ENSG00000150712 MTMR12 lung pneumocytes Medium Supported Q9C0I1 54545 +ENSG00000150753 CCT5 bronchus respiratory epithelial cells Low Enhanced P48643 22948 +ENSG00000150753 CCT5 lung macrophages Medium Enhanced P48643 22948 +ENSG00000150768 DLAT bronchus respiratory epithelial cells High Enhanced P10515 1737 +ENSG00000150768 DLAT lung macrophages Low Enhanced P10515 1737 +ENSG00000150782 IL18 bronchus respiratory epithelial cells High Enhanced Q14116 3606 +ENSG00000150782 IL18 lung macrophages High Enhanced Q14116 3606 +ENSG00000150867 PIP4K2A bronchus respiratory epithelial cells High Supported P48426 5305 +ENSG00000150867 PIP4K2A lung macrophages Medium Supported P48426 5305 +ENSG00000150867 PIP4K2A lung pneumocytes Medium Supported P48426 5305 +ENSG00000150938 CRIM1 bronchus respiratory epithelial cells Medium Enhanced Q9NZV1 51232 +ENSG00000150938 CRIM1 lung macrophages Medium Enhanced Q9NZV1 51232 +ENSG00000150990 DHX37 lung pneumocytes Low Enhanced Q8IY37 57647 +ENSG00000150991 UBC bronchus respiratory epithelial cells High Supported P0CG48 7316 +ENSG00000150991 UBC lung macrophages Medium Supported P0CG48 7316 +ENSG00000150991 UBC lung pneumocytes Medium Supported P0CG48 7316 +ENSG00000151023 ENKUR bronchus respiratory epithelial cells Low Enhanced Q8TC29 219670 +ENSG00000151067 CACNA1C bronchus respiratory epithelial cells Low Enhanced Q13936 775 +ENSG00000151067 CACNA1C lung macrophages Low Enhanced Q13936 775 +ENSG00000151067 CACNA1C lung pneumocytes Medium Enhanced Q13936 775 +ENSG00000151093 OXSM bronchus respiratory epithelial cells Medium Enhanced Q9NWU1 54995 +ENSG00000151093 OXSM lung macrophages Medium Enhanced Q9NWU1 54995 +ENSG00000151093 OXSM lung pneumocytes Low Enhanced Q9NWU1 54995 +ENSG00000151240 DIP2C bronchus respiratory epithelial cells Medium Enhanced Q9Y2E4 22982 +ENSG00000151240 DIP2C lung macrophages High Enhanced Q9Y2E4 22982 +ENSG00000151240 DIP2C lung pneumocytes High Enhanced Q9Y2E4 22982 +ENSG00000151247 EIF4E bronchus respiratory epithelial cells Medium Supported P06730 1977 +ENSG00000151247 EIF4E lung macrophages Medium Supported P06730 1977 +ENSG00000151247 EIF4E lung pneumocytes Low Supported P06730 1977 +ENSG00000151276 MAGI1 bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000151276 MAGI1 lung macrophages Low Enhanced NA NA +ENSG00000151332 MBIP bronchus respiratory epithelial cells Low Supported Q9NS73 51562 +ENSG00000151332 MBIP lung macrophages Low Supported Q9NS73 51562 +ENSG00000151332 MBIP lung pneumocytes Low Supported Q9NS73 51562 +ENSG00000151338 MIPOL1 bronchus respiratory epithelial cells Medium Enhanced Q8TD10 145282 +ENSG00000151338 MIPOL1 lung macrophages Medium Enhanced Q8TD10 145282 +ENSG00000151338 MIPOL1 lung pneumocytes Low Enhanced Q8TD10 145282 +ENSG00000151364 KCTD14 lung pneumocytes Low Enhanced Q9BQ13 65987 +ENSG00000151498 ACAD8 bronchus respiratory epithelial cells High Enhanced Q9UKU7 27034 +ENSG00000151498 ACAD8 lung macrophages Medium Enhanced Q9UKU7 27034 +ENSG00000151500 THYN1 bronchus respiratory epithelial cells Medium Supported Q9P016 29087 +ENSG00000151500 THYN1 lung macrophages High Supported Q9P016 29087 +ENSG00000151500 THYN1 lung pneumocytes High Supported Q9P016 29087 +ENSG00000151532 VTI1A bronchus respiratory epithelial cells Low Supported Q96AJ9 143187 +ENSG00000151532 VTI1A lung macrophages Low Supported Q96AJ9 143187 +ENSG00000151623 NR3C2 bronchus respiratory epithelial cells Medium Enhanced P08235 4306 +ENSG00000151623 NR3C2 lung macrophages High Enhanced P08235 4306 +ENSG00000151623 NR3C2 lung pneumocytes Low Enhanced P08235 4306 +ENSG00000151632 AKR1C2 bronchus respiratory epithelial cells Low Enhanced P52895 1646 +ENSG00000151689 INPP1 bronchus respiratory epithelial cells Low Supported P49441 3628 +ENSG00000151689 INPP1 lung macrophages Medium Supported P49441 3628 +ENSG00000151726 ACSL1 bronchus respiratory epithelial cells Medium Enhanced P33121 2180 +ENSG00000151726 ACSL1 lung macrophages High Enhanced P33121 2180 +ENSG00000151726 ACSL1 lung pneumocytes Medium Enhanced P33121 2180 +ENSG00000151882 CCL28 lung macrophages Low Supported Q9NRJ3 56477 +ENSG00000151917 BEND6 bronchus respiratory epithelial cells Medium Enhanced Q5SZJ8 221336 +ENSG00000151929 BAG3 bronchus respiratory epithelial cells Medium Enhanced O95817 9531 +ENSG00000151929 BAG3 lung pneumocytes Medium Enhanced O95817 9531 +ENSG00000152133 GPATCH11 bronchus respiratory epithelial cells High Enhanced Q8N954 253635 +ENSG00000152133 GPATCH11 lung macrophages High Enhanced Q8N954 253635 +ENSG00000152133 GPATCH11 lung pneumocytes High Enhanced Q8N954 253635 +ENSG00000152193 RNF219 bronchus respiratory epithelial cells Medium Enhanced Q5W0B1 79596 +ENSG00000152193 RNF219 lung macrophages Medium Enhanced Q5W0B1 79596 +ENSG00000152193 RNF219 lung pneumocytes Low Enhanced Q5W0B1 79596 +ENSG00000152234 ATP5A1 bronchus respiratory epithelial cells High Enhanced P25705 498 +ENSG00000152234 ATP5A1 lung macrophages High Enhanced P25705 498 +ENSG00000152234 ATP5A1 lung pneumocytes High Enhanced P25705 498 +ENSG00000152240 HAUS1 bronchus respiratory epithelial cells High Supported Q96CS2 115106 +ENSG00000152240 HAUS1 lung macrophages Medium Supported Q96CS2 115106 +ENSG00000152291 TGOLN2 bronchus respiratory epithelial cells Medium Enhanced O43493 10618 +ENSG00000152291 TGOLN2 lung macrophages Medium Enhanced O43493 10618 +ENSG00000152291 TGOLN2 lung pneumocytes Medium Enhanced O43493 10618 +ENSG00000152422 XRCC4 bronchus respiratory epithelial cells High Enhanced Q13426 7518 +ENSG00000152422 XRCC4 lung macrophages High Enhanced Q13426 7518 +ENSG00000152422 XRCC4 lung pneumocytes High Enhanced Q13426 7518 +ENSG00000152582 SPEF2 bronchus respiratory epithelial cells Medium Enhanced Q9C093 79925 +ENSG00000152583 SPARCL1 bronchus respiratory epithelial cells Low Enhanced Q14515 8404 +ENSG00000152601 MBNL1 bronchus respiratory epithelial cells Medium Enhanced Q9NR56 4154 +ENSG00000152601 MBNL1 lung macrophages Low Enhanced Q9NR56 4154 +ENSG00000152601 MBNL1 lung pneumocytes Medium Enhanced Q9NR56 4154 +ENSG00000152611 CAPSL bronchus respiratory epithelial cells Medium Enhanced Q8WWF8 133690 +ENSG00000152620 NADK2 bronchus respiratory epithelial cells Low Enhanced Q4G0N4 133686 +ENSG00000152620 NADK2 lung macrophages Medium Enhanced Q4G0N4 133686 +ENSG00000152661 GJA1 lung macrophages Low Enhanced P17302 2697 +ENSG00000152661 GJA1 lung pneumocytes Low Enhanced P17302 2697 +ENSG00000152700 SAR1B bronchus respiratory epithelial cells Medium Supported Q9Y6B6 51128 +ENSG00000152700 SAR1B lung macrophages Medium Supported Q9Y6B6 51128 +ENSG00000152795 HNRNPDL bronchus respiratory epithelial cells High Supported O14979 9987 +ENSG00000152795 HNRNPDL lung macrophages Medium Supported O14979 9987 +ENSG00000152795 HNRNPDL lung pneumocytes High Supported O14979 9987 +ENSG00000152818 UTRN bronchus respiratory epithelial cells High Enhanced P46939 7402 +ENSG00000152818 UTRN lung macrophages Medium Enhanced P46939 7402 +ENSG00000152818 UTRN lung pneumocytes Medium Enhanced P46939 7402 +ENSG00000152904 GGPS1 lung macrophages Low Enhanced O95749 9453 +ENSG00000153046 CDYL bronchus respiratory epithelial cells High Enhanced Q9Y232 9425 +ENSG00000153046 CDYL lung macrophages Medium Enhanced Q9Y232 9425 +ENSG00000153046 CDYL lung pneumocytes Low Enhanced Q9Y232 9425 +ENSG00000153066 TXNDC11 bronchus respiratory epithelial cells Medium Supported Q6PKC3 51061 +ENSG00000153066 TXNDC11 lung macrophages High Supported Q6PKC3 51061 +ENSG00000153066 TXNDC11 lung pneumocytes Medium Supported Q6PKC3 51061 +ENSG00000153071 DAB2 bronchus respiratory epithelial cells Medium Enhanced P98082 1601 +ENSG00000153071 DAB2 lung macrophages Medium Enhanced P98082 1601 +ENSG00000153071 DAB2 lung pneumocytes Low Enhanced P98082 1601 +ENSG00000153147 SMARCA5 bronchus respiratory epithelial cells Medium Supported O60264 8467 +ENSG00000153147 SMARCA5 lung macrophages Medium Supported O60264 8467 +ENSG00000153147 SMARCA5 lung pneumocytes Medium Supported O60264 8467 +ENSG00000153179 RASSF3 bronchus respiratory epithelial cells High Supported Q86WH2 283349 +ENSG00000153179 RASSF3 lung macrophages High Supported Q86WH2 283349 +ENSG00000153179 RASSF3 lung pneumocytes Low Supported Q86WH2 283349 +ENSG00000153187 HNRNPU bronchus respiratory epithelial cells High Supported Q00839 3192 +ENSG00000153187 HNRNPU lung macrophages High Supported Q00839 3192 +ENSG00000153187 HNRNPU lung pneumocytes High Supported Q00839 3192 +ENSG00000153201 RANBP2 bronchus respiratory epithelial cells High Supported P49792 5903 +ENSG00000153201 RANBP2 lung macrophages Low Supported P49792 5903 +ENSG00000153201 RANBP2 lung pneumocytes Medium Supported P49792 5903 +ENSG00000153283 CD96 lung macrophages Low Enhanced P40200 10225 +ENSG00000153395 LPCAT1 bronchus respiratory epithelial cells High Enhanced Q8NF37 79888 +ENSG00000153395 LPCAT1 lung pneumocytes High Enhanced Q8NF37 79888 +ENSG00000153563 CD8A lung macrophages Low Enhanced P01732 925 +ENSG00000153767 GTF2E1 bronchus respiratory epithelial cells High Enhanced P29083 2960 +ENSG00000153767 GTF2E1 lung macrophages High Enhanced P29083 2960 +ENSG00000153767 GTF2E1 lung pneumocytes High Enhanced P29083 2960 +ENSG00000153789 FAM92B bronchus respiratory epithelial cells High Enhanced Q6ZTR7 339145 +ENSG00000153820 SPHKAP bronchus respiratory epithelial cells Low Enhanced Q2M3C7 80309 +ENSG00000153820 SPHKAP lung macrophages Low Enhanced Q2M3C7 80309 +ENSG00000153827 TRIP12 bronchus respiratory epithelial cells Medium Enhanced Q14669 9320 +ENSG00000153827 TRIP12 lung macrophages Medium Enhanced Q14669 9320 +ENSG00000153827 TRIP12 lung pneumocytes Medium Enhanced Q14669 9320 +ENSG00000153879 CEBPG bronchus respiratory epithelial cells Low Enhanced P53567 1054 +ENSG00000153879 CEBPG lung macrophages Medium Enhanced P53567 1054 +ENSG00000153904 DDAH1 bronchus respiratory epithelial cells High Enhanced O94760 23576 +ENSG00000153904 DDAH1 lung macrophages High Enhanced O94760 23576 +ENSG00000153904 DDAH1 lung pneumocytes Medium Enhanced O94760 23576 +ENSG00000153914 SREK1 bronchus respiratory epithelial cells High Enhanced Q8WXA9 140890 +ENSG00000153914 SREK1 lung macrophages Medium Enhanced Q8WXA9 140890 +ENSG00000153914 SREK1 lung pneumocytes Medium Enhanced Q8WXA9 140890 +ENSG00000153936 HS2ST1 bronchus respiratory epithelial cells Medium Supported Q7LGA3 9653 +ENSG00000153936 HS2ST1 lung macrophages Medium Supported Q7LGA3 9653 +ENSG00000153989 NUS1 lung pneumocytes Low Supported Q96E22 116150 +ENSG00000154079 SDHAF4 bronchus respiratory epithelial cells High Supported Q5VUM1 135154 +ENSG00000154079 SDHAF4 lung macrophages Medium Supported Q5VUM1 135154 +ENSG00000154079 SDHAF4 lung pneumocytes Medium Supported Q5VUM1 135154 +ENSG00000154099 DNAAF1 bronchus respiratory epithelial cells High Enhanced Q8NEP3 123872 +ENSG00000154174 TOMM70 bronchus respiratory epithelial cells High Enhanced O94826 9868 +ENSG00000154174 TOMM70 lung macrophages Low Enhanced O94826 9868 +ENSG00000154188 ANGPT1 lung macrophages Low Enhanced Q15389 284 +ENSG00000154229 PRKCA bronchus respiratory epithelial cells Medium Enhanced P17252 5578 +ENSG00000154229 PRKCA lung macrophages Medium Enhanced P17252 5578 +ENSG00000154274 C4orf19 bronchus respiratory epithelial cells Low Enhanced Q8IY42 55286 +ENSG00000154305 MIA3 bronchus respiratory epithelial cells Medium Enhanced Q5JRA6 375056 +ENSG00000154358 OBSCN bronchus respiratory epithelial cells Medium Enhanced Q5VST9 84033 +ENSG00000154358 OBSCN lung macrophages Low Enhanced Q5VST9 84033 +ENSG00000154358 OBSCN lung pneumocytes Low Enhanced Q5VST9 84033 +ENSG00000154380 ENAH bronchus respiratory epithelial cells Medium Enhanced Q8N8S7 55740 +ENSG00000154380 ENAH lung macrophages Low Enhanced Q8N8S7 55740 +ENSG00000154380 ENAH lung pneumocytes Medium Enhanced Q8N8S7 55740 +ENSG00000154473 BUB3 bronchus respiratory epithelial cells Medium Supported O43684 9184 +ENSG00000154473 BUB3 lung macrophages Medium Supported O43684 9184 +ENSG00000154473 BUB3 lung pneumocytes High Supported O43684 9184 +ENSG00000154556 SORBS2 bronchus respiratory epithelial cells Medium Supported O94875 8470 +ENSG00000154556 SORBS2 lung macrophages Medium Supported O94875 8470 +ENSG00000154556 SORBS2 lung pneumocytes Medium Supported O94875 8470 +ENSG00000154639 CXADR bronchus respiratory epithelial cells Medium Enhanced P78310 1525 +ENSG00000154639 CXADR lung macrophages Low Enhanced P78310 1525 +ENSG00000154654 NCAM2 bronchus respiratory epithelial cells Low Supported O15394 4685 +ENSG00000154723 ATP5J bronchus respiratory epithelial cells High Supported P18859 522 +ENSG00000154723 ATP5J lung macrophages High Supported P18859 522 +ENSG00000154723 ATP5J lung pneumocytes High Supported P18859 522 +ENSG00000154727 GABPA bronchus respiratory epithelial cells Medium Supported Q06546 2551 +ENSG00000154727 GABPA lung macrophages Low Supported Q06546 2551 +ENSG00000154727 GABPA lung pneumocytes Medium Supported Q06546 2551 +ENSG00000154767 XPC bronchus respiratory epithelial cells Medium Supported Q01831 7508 +ENSG00000154767 XPC lung macrophages Medium Supported Q01831 7508 +ENSG00000154767 XPC lung pneumocytes Medium Supported Q01831 7508 +ENSG00000154803 FLCN bronchus respiratory epithelial cells High Supported Q8NFG4 201163 +ENSG00000154803 FLCN lung macrophages Medium Supported Q8NFG4 201163 +ENSG00000154803 FLCN lung pneumocytes Medium Supported Q8NFG4 201163 +ENSG00000154832 CXXC1 bronchus respiratory epithelial cells High Supported Q9P0U4 30827 +ENSG00000154832 CXXC1 lung macrophages High Supported Q9P0U4 30827 +ENSG00000154832 CXXC1 lung pneumocytes Medium Supported Q9P0U4 30827 +ENSG00000154864 PIEZO2 bronchus respiratory epithelial cells Low Enhanced Q9H5I5 63895 +ENSG00000154864 PIEZO2 lung macrophages Medium Enhanced Q9H5I5 63895 +ENSG00000154864 PIEZO2 lung pneumocytes Low Enhanced Q9H5I5 63895 +ENSG00000154920 EME1 bronchus respiratory epithelial cells High Supported Q96AY2 146956 +ENSG00000154920 EME1 lung macrophages Medium Supported Q96AY2 146956 +ENSG00000154920 EME1 lung pneumocytes High Supported Q96AY2 146956 +ENSG00000154930 ACSS1 bronchus respiratory epithelial cells High Enhanced Q9NUB1 84532 +ENSG00000154930 ACSS1 lung macrophages Medium Enhanced Q9NUB1 84532 +ENSG00000154930 ACSS1 lung pneumocytes Low Enhanced Q9NUB1 84532 +ENSG00000155008 APOOL bronchus respiratory epithelial cells Medium Enhanced Q6UXV4 139322 +ENSG00000155008 APOOL lung pneumocytes Low Enhanced Q6UXV4 139322 +ENSG00000155026 RSPH10B bronchus respiratory epithelial cells Medium Supported P0C881 222967 +ENSG00000155066 PROM2 bronchus respiratory epithelial cells Medium Enhanced Q8N271 150696 +ENSG00000155085 AK9 bronchus respiratory epithelial cells High Enhanced Q5TCS8 221264 +ENSG00000155085 AK9 lung macrophages High Enhanced Q5TCS8 221264 +ENSG00000155085 AK9 lung pneumocytes High Enhanced Q5TCS8 221264 +ENSG00000155100 OTUD6B bronchus respiratory epithelial cells Medium Enhanced Q8N6M0 51633 +ENSG00000155100 OTUD6B lung macrophages High Enhanced Q8N6M0 51633 +ENSG00000155100 OTUD6B lung pneumocytes Medium Enhanced Q8N6M0 51633 +ENSG00000155324 GRAMD3 bronchus respiratory epithelial cells Medium Enhanced Q96HH9 65983 +ENSG00000155324 GRAMD3 lung macrophages Medium Enhanced Q96HH9 65983 +ENSG00000155324 GRAMD3 lung pneumocytes Low Enhanced Q96HH9 65983 +ENSG00000155380 SLC16A1 bronchus respiratory epithelial cells Low Enhanced NA NA +ENSG00000155380 SLC16A1 lung macrophages Low Enhanced NA NA +ENSG00000155438 NIFK bronchus respiratory epithelial cells Low Supported Q9BYG3 84365 +ENSG00000155438 NIFK lung macrophages Low Supported Q9BYG3 84365 +ENSG00000155465 SLC7A7 bronchus respiratory epithelial cells Low Enhanced Q9UM01 9056 +ENSG00000155465 SLC7A7 lung macrophages Low Enhanced Q9UM01 9056 +ENSG00000155506 LARP1 bronchus respiratory epithelial cells Medium Supported Q6PKG0 23367 +ENSG00000155506 LARP1 lung macrophages Low Supported Q6PKG0 23367 +ENSG00000155629 PIK3AP1 lung macrophages Medium Enhanced Q6ZUJ8 118788 +ENSG00000155660 PDIA4 bronchus respiratory epithelial cells High Supported P13667 9601 +ENSG00000155660 PDIA4 lung macrophages High Supported P13667 9601 +ENSG00000155660 PDIA4 lung pneumocytes Medium Supported P13667 9601 +ENSG00000155755 TMEM237 bronchus respiratory epithelial cells High Enhanced Q96Q45 65062 +ENSG00000155755 TMEM237 lung macrophages Low Enhanced Q96Q45 65062 +ENSG00000155761 SPAG17 bronchus respiratory epithelial cells Medium Enhanced Q6Q759 200162 +ENSG00000155792 DEPTOR bronchus respiratory epithelial cells Medium Enhanced Q8TB45 64798 +ENSG00000155827 RNF20 bronchus respiratory epithelial cells Medium Supported Q5VTR2 56254 +ENSG00000155827 RNF20 lung macrophages Medium Supported Q5VTR2 56254 +ENSG00000155827 RNF20 lung pneumocytes Medium Supported Q5VTR2 56254 +ENSG00000155850 SLC26A2 bronchus respiratory epithelial cells Low Enhanced P50443 1836 +ENSG00000155875 SAXO1 bronchus respiratory epithelial cells Low Enhanced Q8IYX7 158297 +ENSG00000155876 RRAGA bronchus respiratory epithelial cells Medium Supported Q7L523 10670 +ENSG00000155876 RRAGA lung macrophages High Supported Q7L523 10670 +ENSG00000155897 ADCY8 bronchus respiratory epithelial cells Medium Supported P40145 114 +ENSG00000155897 ADCY8 lung macrophages Low Supported P40145 114 +ENSG00000155897 ADCY8 lung pneumocytes Low Supported P40145 114 +ENSG00000155975 VPS37A bronchus respiratory epithelial cells Medium Enhanced Q8NEZ2 137492 +ENSG00000155975 VPS37A lung macrophages Medium Enhanced Q8NEZ2 137492 +ENSG00000156042 CFAP70 bronchus respiratory epithelial cells High Enhanced Q5T0N1 118491 +ENSG00000156171 DRAM2 bronchus respiratory epithelial cells High Enhanced Q6UX65 128338 +ENSG00000156171 DRAM2 lung macrophages Medium Enhanced Q6UX65 128338 +ENSG00000156232 WHAMM bronchus respiratory epithelial cells Medium Supported Q8TF30 123720 +ENSG00000156232 WHAMM lung macrophages Low Supported Q8TF30 123720 +ENSG00000156232 WHAMM lung pneumocytes Medium Supported Q8TF30 123720 +ENSG00000156256 USP16 bronchus respiratory epithelial cells Medium Supported Q9Y5T5 10600 +ENSG00000156256 USP16 lung macrophages Medium Supported Q9Y5T5 10600 +ENSG00000156256 USP16 lung pneumocytes Medium Supported Q9Y5T5 10600 +ENSG00000156261 CCT8 bronchus respiratory epithelial cells High Enhanced P50990 10694 +ENSG00000156261 CCT8 lung macrophages Medium Enhanced P50990 10694 +ENSG00000156261 CCT8 lung pneumocytes Low Enhanced P50990 10694 +ENSG00000156284 CLDN8 bronchus respiratory epithelial cells High Supported P56748 9073 +ENSG00000156284 CLDN8 lung macrophages Low Supported P56748 9073 +ENSG00000156284 CLDN8 lung pneumocytes Medium Supported P56748 9073 +ENSG00000156304 SCAF4 bronchus respiratory epithelial cells High Enhanced O95104 57466 +ENSG00000156304 SCAF4 lung macrophages Medium Enhanced O95104 57466 +ENSG00000156304 SCAF4 lung pneumocytes Medium Enhanced O95104 57466 +ENSG00000156345 CDK20 bronchus respiratory epithelial cells Medium Enhanced Q8IZL9 23552 +ENSG00000156345 CDK20 lung macrophages Medium Enhanced Q8IZL9 23552 +ENSG00000156398 SFXN2 bronchus respiratory epithelial cells Medium Enhanced Q96NB2 118980 +ENSG00000156398 SFXN2 lung macrophages Low Enhanced Q96NB2 118980 +ENSG00000156398 SFXN2 lung pneumocytes Low Enhanced Q96NB2 118980 +ENSG00000156411 C14orf2 bronchus respiratory epithelial cells High Enhanced P56378 9556 +ENSG00000156411 C14orf2 lung macrophages Medium Enhanced P56378 9556 +ENSG00000156411 C14orf2 lung pneumocytes Medium Enhanced P56378 9556 +ENSG00000156453 PCDH1 bronchus respiratory epithelial cells Low Enhanced Q08174 5097 +ENSG00000156453 PCDH1 lung macrophages Low Enhanced Q08174 5097 +ENSG00000156453 PCDH1 lung pneumocytes Low Enhanced Q08174 5097 +ENSG00000156502 SUPV3L1 bronchus respiratory epithelial cells High Enhanced Q8IYB8 6832 +ENSG00000156502 SUPV3L1 lung macrophages Medium Enhanced Q8IYB8 6832 +ENSG00000156502 SUPV3L1 lung pneumocytes Low Enhanced Q8IYB8 6832 +ENSG00000156504 FAM122B lung macrophages Low Enhanced Q7Z309 159090 +ENSG00000156504 FAM122B lung pneumocytes Low Enhanced Q7Z309 159090 +ENSG00000156508 EEF1A1 bronchus respiratory epithelial cells High Supported P68104 1915 +ENSG00000156508 EEF1A1 lung macrophages Low Supported P68104 1915 +ENSG00000156508 EEF1A1 lung pneumocytes Medium Supported P68104 1915 +ENSG00000156515 HK1 bronchus respiratory epithelial cells High Supported P19367 3098 +ENSG00000156515 HK1 lung macrophages Medium Supported P19367 3098 +ENSG00000156515 HK1 lung pneumocytes Low Supported P19367 3098 +ENSG00000156531 PHF6 bronchus respiratory epithelial cells Medium Enhanced Q8IWS0 84295 +ENSG00000156531 PHF6 lung macrophages Medium Enhanced Q8IWS0 84295 +ENSG00000156531 PHF6 lung pneumocytes Medium Enhanced Q8IWS0 84295 +ENSG00000156587 UBE2L6 bronchus respiratory epithelial cells Medium Enhanced O14933 9246 +ENSG00000156587 UBE2L6 lung macrophages High Enhanced O14933 9246 +ENSG00000156587 UBE2L6 lung pneumocytes High Enhanced O14933 9246 +ENSG00000156650 KAT6B bronchus respiratory epithelial cells High Supported NA NA +ENSG00000156650 KAT6B lung macrophages High Supported NA NA +ENSG00000156650 KAT6B lung pneumocytes High Supported NA NA +ENSG00000156675 RAB11FIP1 bronchus respiratory epithelial cells Medium Enhanced Q6WKZ4 80223 +ENSG00000156675 RAB11FIP1 lung macrophages Medium Enhanced Q6WKZ4 80223 +ENSG00000156675 RAB11FIP1 lung pneumocytes Medium Enhanced Q6WKZ4 80223 +ENSG00000156709 AIFM1 bronchus respiratory epithelial cells Medium Enhanced O95831 9131 +ENSG00000156709 AIFM1 lung macrophages Medium Enhanced O95831 9131 +ENSG00000156711 MAPK13 bronchus respiratory epithelial cells High Enhanced O15264 5603 +ENSG00000156711 MAPK13 lung macrophages Medium Enhanced O15264 5603 +ENSG00000156711 MAPK13 lung pneumocytes Medium Enhanced O15264 5603 +ENSG00000156802 ATAD2 bronchus respiratory epithelial cells Medium Enhanced Q6PL18 29028 +ENSG00000156831 NSMCE2 bronchus respiratory epithelial cells High Supported Q96MF7 286053 +ENSG00000156831 NSMCE2 lung macrophages High Supported Q96MF7 286053 +ENSG00000156831 NSMCE2 lung pneumocytes High Supported Q96MF7 286053 +ENSG00000156966 B3GNT7 bronchus respiratory epithelial cells Low Enhanced Q8NFL0 93010 +ENSG00000156983 BRPF1 bronchus respiratory epithelial cells Low Enhanced P55201 7862 +ENSG00000156983 BRPF1 lung macrophages Medium Enhanced P55201 7862 +ENSG00000156983 BRPF1 lung pneumocytes High Enhanced P55201 7862 +ENSG00000157036 EXOG bronchus respiratory epithelial cells Low Enhanced Q9Y2C4 9941 +ENSG00000157036 EXOG lung macrophages Medium Enhanced Q9Y2C4 9941 +ENSG00000157107 FCHO2 bronchus respiratory epithelial cells Low Enhanced Q0JRZ9 115548 +ENSG00000157107 FCHO2 lung macrophages Medium Enhanced Q0JRZ9 115548 +ENSG00000157107 FCHO2 lung pneumocytes Medium Enhanced Q0JRZ9 115548 +ENSG00000157110 RBPMS bronchus respiratory epithelial cells Low Enhanced Q93062 11030 +ENSG00000157110 RBPMS lung pneumocytes High Enhanced Q93062 11030 +ENSG00000157184 CPT2 bronchus respiratory epithelial cells Low Enhanced P23786 1376 +ENSG00000157184 CPT2 lung macrophages High Enhanced P23786 1376 +ENSG00000157212 PAXIP1 bronchus respiratory epithelial cells Low Enhanced Q6ZW49 22976 +ENSG00000157212 PAXIP1 lung macrophages High Enhanced Q6ZW49 22976 +ENSG00000157212 PAXIP1 lung pneumocytes High Enhanced Q6ZW49 22976 +ENSG00000157404 KIT lung macrophages Medium Enhanced P10721 3815 +ENSG00000157450 RNF111 bronchus respiratory epithelial cells Medium Enhanced Q6ZNA4 54778 +ENSG00000157450 RNF111 lung macrophages Medium Enhanced Q6ZNA4 54778 +ENSG00000157450 RNF111 lung pneumocytes Medium Enhanced Q6ZNA4 54778 +ENSG00000157456 CCNB2 bronchus respiratory epithelial cells Low Enhanced O95067 9133 +ENSG00000157470 FAM81A bronchus respiratory epithelial cells Medium Enhanced Q8TBF8 145773 +ENSG00000157470 FAM81A lung macrophages Low Enhanced Q8TBF8 145773 +ENSG00000157502 MUM1L1 bronchus respiratory epithelial cells Low Enhanced Q5H9M0 139221 +ENSG00000157578 LCA5L bronchus respiratory epithelial cells Medium Enhanced O95447 150082 +ENSG00000157613 CREB3L1 bronchus respiratory epithelial cells Medium Enhanced Q96BA8 90993 +ENSG00000157613 CREB3L1 lung macrophages Medium Enhanced Q96BA8 90993 +ENSG00000157617 C2CD2 bronchus respiratory epithelial cells Medium Enhanced Q9Y426 25966 +ENSG00000157617 C2CD2 lung macrophages Low Enhanced Q9Y426 25966 +ENSG00000157637 SLC38A10 bronchus respiratory epithelial cells Medium Enhanced Q9HBR0 124565 +ENSG00000157637 SLC38A10 lung macrophages Medium Enhanced Q9HBR0 124565 +ENSG00000157637 SLC38A10 lung pneumocytes Low Enhanced Q9HBR0 124565 +ENSG00000157765 SLC34A2 bronchus respiratory epithelial cells Low Enhanced O95436 10568 +ENSG00000157765 SLC34A2 lung pneumocytes High Enhanced O95436 10568 +ENSG00000157827 FMNL2 lung macrophages Low Enhanced Q96PY5 114793 +ENSG00000157916 RER1 bronchus respiratory epithelial cells High Supported O15258 11079 +ENSG00000157916 RER1 lung macrophages Medium Supported O15258 11079 +ENSG00000157916 RER1 lung pneumocytes Low Supported O15258 11079 +ENSG00000157992 KRTCAP3 bronchus respiratory epithelial cells High Enhanced Q53RY4 200634 +ENSG00000158023 WDR66 bronchus respiratory epithelial cells Medium Supported Q8TBY9 144406 +ENSG00000158023 WDR66 lung macrophages Medium Supported Q8TBY9 144406 +ENSG00000158023 WDR66 lung pneumocytes Medium Supported Q8TBY9 144406 +ENSG00000158055 GRHL3 bronchus respiratory epithelial cells Medium Enhanced Q8TE85 57822 +ENSG00000158055 GRHL3 lung macrophages Low Enhanced Q8TE85 57822 +ENSG00000158092 NCK1 bronchus respiratory epithelial cells High Supported P16333 4690 +ENSG00000158092 NCK1 lung macrophages High Supported P16333 4690 +ENSG00000158158 CNNM4 bronchus respiratory epithelial cells Medium Enhanced Q6P4Q7 26504 +ENSG00000158158 CNNM4 lung macrophages Low Enhanced Q6P4Q7 26504 +ENSG00000158195 WASF2 bronchus respiratory epithelial cells Medium Enhanced Q9Y6W5 10163 +ENSG00000158195 WASF2 lung macrophages High Enhanced Q9Y6W5 10163 +ENSG00000158270 COLEC12 lung macrophages Low Enhanced Q5KU26 81035 +ENSG00000158290 CUL4B bronchus respiratory epithelial cells Medium Enhanced Q13620 8450 +ENSG00000158301 GPRASP2 bronchus respiratory epithelial cells High Enhanced Q96D09 100528062; 114928 +ENSG00000158373 HIST1H2BD bronchus respiratory epithelial cells High Supported P58876 3017 +ENSG00000158373 HIST1H2BD lung macrophages High Supported P58876 3017 +ENSG00000158373 HIST1H2BD lung pneumocytes High Supported P58876 3017 +ENSG00000158406 HIST1H4H bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000158406 HIST1H4H lung pneumocytes Low Supported NA NA +ENSG00000158428 CATIP bronchus respiratory epithelial cells High Supported Q7Z7H3 375307 +ENSG00000158517 NCF1 lung macrophages High Enhanced P14598 653361 +ENSG00000158545 ZC3H18 bronchus respiratory epithelial cells High Enhanced Q86VM9 124245 +ENSG00000158545 ZC3H18 lung macrophages High Enhanced Q86VM9 124245 +ENSG00000158545 ZC3H18 lung pneumocytes High Enhanced Q86VM9 124245 +ENSG00000158560 DYNC1I1 bronchus respiratory epithelial cells Low Enhanced O14576 1780 +ENSG00000158636 EMSY bronchus respiratory epithelial cells High Supported Q7Z589 56946 +ENSG00000158636 EMSY lung macrophages High Supported Q7Z589 56946 +ENSG00000158636 EMSY lung pneumocytes High Supported Q7Z589 56946 +ENSG00000158714 SLAMF8 lung macrophages Medium Enhanced Q9P0V8 56833 +ENSG00000158769 F11R bronchus respiratory epithelial cells Medium Enhanced Q9Y624 50848 +ENSG00000158769 F11R lung macrophages Low Enhanced Q9Y624 50848 +ENSG00000158769 F11R lung pneumocytes Low Enhanced Q9Y624 50848 +ENSG00000158773 USF1 bronchus respiratory epithelial cells High Supported P22415 7391 +ENSG00000158773 USF1 lung macrophages Medium Supported P22415 7391 +ENSG00000158773 USF1 lung pneumocytes Medium Supported P22415 7391 +ENSG00000158806 NPM2 bronchus respiratory epithelial cells High Enhanced Q86SE8 10361 +ENSG00000158864 NDUFS2 bronchus respiratory epithelial cells High Enhanced O75306 4720 +ENSG00000158869 FCER1G bronchus respiratory epithelial cells Low Supported P30273 2207 +ENSG00000158869 FCER1G lung macrophages High Supported P30273 2207 +ENSG00000158869 FCER1G lung pneumocytes Medium Supported P30273 2207 +ENSG00000158887 MPZ bronchus respiratory epithelial cells Low Supported P25189 4359 +ENSG00000158941 CCAR2 bronchus respiratory epithelial cells High Enhanced Q8N163 57805 +ENSG00000158985 CDC42SE2 bronchus respiratory epithelial cells Low Enhanced Q9NRR3 56990 +ENSG00000158985 CDC42SE2 lung macrophages Low Enhanced Q9NRR3 56990 +ENSG00000158985 CDC42SE2 lung pneumocytes Low Enhanced Q9NRR3 56990 +ENSG00000159055 MIS18A bronchus respiratory epithelial cells Low Enhanced Q9NYP9 54069 +ENSG00000159055 MIS18A lung macrophages Low Enhanced Q9NYP9 54069 +ENSG00000159079 C21orf59 bronchus respiratory epithelial cells High Enhanced P57076 56683 +ENSG00000159079 C21orf59 lung macrophages Low Enhanced P57076 56683 +ENSG00000159082 SYNJ1 bronchus respiratory epithelial cells Medium Enhanced O43426 8867 +ENSG00000159082 SYNJ1 lung macrophages Medium Enhanced O43426 8867 +ENSG00000159082 SYNJ1 lung pneumocytes Low Enhanced O43426 8867 +ENSG00000159111 MRPL10 bronchus respiratory epithelial cells Medium Enhanced Q7Z7H8 124995 +ENSG00000159128 IFNGR2 bronchus respiratory epithelial cells High Enhanced B5MCZ0 NA +ENSG00000159128 IFNGR2 lung macrophages Medium Enhanced B5MCZ0 NA +ENSG00000159128 IFNGR2 lung pneumocytes Medium Enhanced B5MCZ0 NA +ENSG00000159140 SON bronchus respiratory epithelial cells Medium Supported P18583 6651 +ENSG00000159140 SON lung macrophages Medium Supported P18583 6651 +ENSG00000159140 SON lung pneumocytes Medium Supported P18583 6651 +ENSG00000159189 C1QC bronchus respiratory epithelial cells Low Supported P02747 714 +ENSG00000159189 C1QC lung macrophages Low Supported P02747 714 +ENSG00000159208 CIART bronchus respiratory epithelial cells Medium Enhanced Q8N365 148523 +ENSG00000159212 CLIC6 bronchus respiratory epithelial cells High Enhanced Q96NY7 54102 +ENSG00000159212 CLIC6 lung pneumocytes Medium Enhanced Q96NY7 54102 +ENSG00000159216 RUNX1 bronchus respiratory epithelial cells Medium Enhanced Q01196 861 +ENSG00000159216 RUNX1 lung macrophages Medium Enhanced Q01196 861 +ENSG00000159217 IGF2BP1 bronchus respiratory epithelial cells Low Enhanced Q9NZI8 10642 +ENSG00000159259 CHAF1B bronchus respiratory epithelial cells Low Enhanced Q13112 8208 +ENSG00000159348 CYB5R1 bronchus respiratory epithelial cells High Enhanced Q9UHQ9 51706 +ENSG00000159348 CYB5R1 lung macrophages High Enhanced Q9UHQ9 51706 +ENSG00000159352 PSMD4 bronchus respiratory epithelial cells Medium Enhanced P55036 5710 +ENSG00000159352 PSMD4 lung macrophages Medium Enhanced P55036 5710 +ENSG00000159399 HK2 bronchus respiratory epithelial cells Low Enhanced P52789 3099 +ENSG00000159399 HK2 lung macrophages Medium Enhanced P52789 3099 +ENSG00000159399 HK2 lung pneumocytes Low Enhanced P52789 3099 +ENSG00000159423 ALDH4A1 bronchus respiratory epithelial cells Medium Enhanced P30038 8659 +ENSG00000159423 ALDH4A1 lung macrophages High Enhanced P30038 8659 +ENSG00000159423 ALDH4A1 lung pneumocytes Medium Enhanced P30038 8659 +ENSG00000159588 CCDC17 bronchus respiratory epithelial cells Medium Enhanced Q96LX7 149483 +ENSG00000159593 NAE1 bronchus respiratory epithelial cells High Enhanced Q13564 8883 +ENSG00000159593 NAE1 lung macrophages Medium Enhanced Q13564 8883 +ENSG00000159593 NAE1 lung pneumocytes Medium Enhanced Q13564 8883 +ENSG00000159640 ACE lung pneumocytes Medium Enhanced P12821 1636 +ENSG00000159658 EFCAB14 bronchus respiratory epithelial cells High Supported O75071 9813 +ENSG00000159658 EFCAB14 lung macrophages Medium Supported O75071 9813 +ENSG00000159658 EFCAB14 lung pneumocytes Medium Supported O75071 9813 +ENSG00000159842 ABR bronchus respiratory epithelial cells Medium Enhanced A0A0D9SGD7 NA +ENSG00000159842 ABR lung macrophages Medium Enhanced A0A0D9SGD7 NA +ENSG00000159842 ABR lung pneumocytes Medium Enhanced A0A0D9SGD7 NA +ENSG00000160049 DFFA bronchus respiratory epithelial cells High Supported O00273 1676 +ENSG00000160049 DFFA lung macrophages Medium Supported O00273 1676 +ENSG00000160049 DFFA lung pneumocytes Low Supported O00273 1676 +ENSG00000160075 SSU72 bronchus respiratory epithelial cells High Enhanced Q9NP77 29101 +ENSG00000160075 SSU72 lung macrophages Low Enhanced Q9NP77 29101 +ENSG00000160075 SSU72 lung pneumocytes Medium Enhanced Q9NP77 29101 +ENSG00000160180 TFF3 bronchus respiratory epithelial cells High Enhanced Q07654 7033 +ENSG00000160188 RSPH1 bronchus respiratory epithelial cells High Enhanced Q8WYR4 89765 +ENSG00000160191 PDE9A bronchus respiratory epithelial cells Low Enhanced O76083 5152 +ENSG00000160191 PDE9A lung macrophages Medium Enhanced O76083 5152 +ENSG00000160194 NDUFV3 bronchus respiratory epithelial cells High Enhanced P56181 4731 +ENSG00000160194 NDUFV3 lung macrophages Medium Enhanced P56181 4731 +ENSG00000160194 NDUFV3 lung pneumocytes Medium Enhanced P56181 4731 +ENSG00000160201 U2AF1 bronchus respiratory epithelial cells High Supported Q01081 102724594; 7307 +ENSG00000160201 U2AF1 lung macrophages High Supported Q01081 102724594; 7307 +ENSG00000160201 U2AF1 lung pneumocytes High Supported Q01081 102724594; 7307 +ENSG00000160208 RRP1B bronchus respiratory epithelial cells High Supported Q14684 23076 +ENSG00000160208 RRP1B lung macrophages Low Supported Q14684 23076 +ENSG00000160208 RRP1B lung pneumocytes Medium Supported Q14684 23076 +ENSG00000160211 G6PD bronchus respiratory epithelial cells Medium Enhanced P11413 2539 +ENSG00000160211 G6PD lung macrophages Medium Enhanced P11413 2539 +ENSG00000160218 TRAPPC10 bronchus respiratory epithelial cells Medium Supported P48553 7109 +ENSG00000160218 TRAPPC10 lung macrophages Medium Supported P48553 7109 +ENSG00000160218 TRAPPC10 lung pneumocytes Low Supported P48553 7109 +ENSG00000160221 C21orf33 bronchus respiratory epithelial cells High Supported P30042 102724023; 8209 +ENSG00000160221 C21orf33 lung macrophages Medium Supported P30042 102724023; 8209 +ENSG00000160221 C21orf33 lung pneumocytes Low Supported P30042 102724023; 8209 +ENSG00000160226 C21orf2 bronchus respiratory epithelial cells Medium Supported O43822 755 +ENSG00000160226 C21orf2 lung macrophages Low Supported O43822 755 +ENSG00000160226 C21orf2 lung pneumocytes Low Supported O43822 755 +ENSG00000160255 ITGB2 lung macrophages Medium Enhanced P05107 3689 +ENSG00000160285 LSS bronchus respiratory epithelial cells High Supported P48449 4047 +ENSG00000160285 LSS lung macrophages High Supported P48449 4047 +ENSG00000160285 LSS lung pneumocytes Medium Supported P48449 4047 +ENSG00000160299 PCNT bronchus respiratory epithelial cells Medium Enhanced O95613 5116 +ENSG00000160299 PCNT lung macrophages Low Enhanced O95613 5116 +ENSG00000160401 CFAP157 bronchus respiratory epithelial cells High Enhanced Q5JU67 286207 +ENSG00000160584 SIK3 bronchus respiratory epithelial cells High Enhanced Q9Y2K2 23387 +ENSG00000160584 SIK3 lung macrophages High Enhanced Q9Y2K2 23387 +ENSG00000160584 SIK3 lung pneumocytes High Enhanced Q9Y2K2 23387 +ENSG00000160606 TLCD1 bronchus respiratory epithelial cells Medium Enhanced Q96CP7 116238 +ENSG00000160606 TLCD1 lung pneumocytes Medium Enhanced Q96CP7 116238 +ENSG00000160633 SAFB bronchus respiratory epithelial cells High Supported Q15424 6294 +ENSG00000160633 SAFB lung macrophages High Supported Q15424 6294 +ENSG00000160633 SAFB lung pneumocytes High Supported Q15424 6294 +ENSG00000160678 S100A1 lung macrophages Low Enhanced P23297 6271 +ENSG00000160683 CXCR5 bronchus respiratory epithelial cells Low Enhanced P32302 643 +ENSG00000160683 CXCR5 lung macrophages Medium Enhanced P32302 643 +ENSG00000160685 ZBTB7B bronchus respiratory epithelial cells High Enhanced O15156 51043 +ENSG00000160691 SHC1 bronchus respiratory epithelial cells High Supported P29353 6464 +ENSG00000160691 SHC1 lung macrophages Medium Supported P29353 6464 +ENSG00000160691 SHC1 lung pneumocytes Low Supported P29353 6464 +ENSG00000160703 NLRX1 bronchus respiratory epithelial cells High Supported Q86UT6 79671 +ENSG00000160703 NLRX1 lung macrophages Medium Supported Q86UT6 79671 +ENSG00000160710 ADAR bronchus respiratory epithelial cells Medium Enhanced P55265 103 +ENSG00000160710 ADAR lung macrophages Low Enhanced P55265 103 +ENSG00000160710 ADAR lung pneumocytes Low Enhanced P55265 103 +ENSG00000160741 CRTC2 bronchus respiratory epithelial cells Medium Supported Q53ET0 200186 +ENSG00000160741 CRTC2 lung macrophages Medium Supported Q53ET0 200186 +ENSG00000160741 CRTC2 lung pneumocytes Medium Supported Q53ET0 200186 +ENSG00000160789 LMNA bronchus respiratory epithelial cells High Supported P02545 4000 +ENSG00000160789 LMNA lung macrophages High Supported P02545 4000 +ENSG00000160789 LMNA lung pneumocytes High Supported P02545 4000 +ENSG00000160813 PPP1R35 bronchus respiratory epithelial cells Medium Enhanced Q8TAP8 221908 +ENSG00000160813 PPP1R35 lung pneumocytes Medium Enhanced Q8TAP8 221908 +ENSG00000160877 NACC1 bronchus respiratory epithelial cells High Supported Q96RE7 112939 +ENSG00000160877 NACC1 lung macrophages Medium Supported Q96RE7 112939 +ENSG00000160877 NACC1 lung pneumocytes Medium Supported Q96RE7 112939 +ENSG00000160883 HK3 lung macrophages High Enhanced P52790 3101 +ENSG00000160948 VPS28 bronchus respiratory epithelial cells Medium Enhanced Q9UK41 51160 +ENSG00000160948 VPS28 lung macrophages Low Enhanced Q9UK41 51160 +ENSG00000160957 RECQL4 bronchus respiratory epithelial cells Medium Supported O94761 9401 +ENSG00000160957 RECQL4 lung macrophages Low Supported O94761 9401 +ENSG00000161011 SQSTM1 bronchus respiratory epithelial cells Medium Supported Q13501 8878 +ENSG00000161011 SQSTM1 lung macrophages Low Supported Q13501 8878 +ENSG00000161011 SQSTM1 lung pneumocytes Low Supported Q13501 8878 +ENSG00000161016 RPL8 bronchus respiratory epithelial cells Medium Enhanced P62917 6132 +ENSG00000161016 RPL8 lung macrophages Low Enhanced P62917 6132 +ENSG00000161016 RPL8 lung pneumocytes Low Enhanced P62917 6132 +ENSG00000161057 PSMC2 bronchus respiratory epithelial cells Medium Supported P35998 5701 +ENSG00000161057 PSMC2 lung macrophages Medium Supported P35998 5701 +ENSG00000161057 PSMC2 lung pneumocytes High Supported P35998 5701 +ENSG00000161265 U2AF1L4 bronchus respiratory epithelial cells High Supported Q8WU68 199746 +ENSG00000161265 U2AF1L4 lung macrophages High Supported Q8WU68 199746 +ENSG00000161265 U2AF1L4 lung pneumocytes High Supported Q8WU68 199746 +ENSG00000161267 BDH1 bronchus respiratory epithelial cells High Enhanced C9JB83 NA +ENSG00000161513 FDXR bronchus respiratory epithelial cells High Enhanced P22570 2232 +ENSG00000161526 SAP30BP bronchus respiratory epithelial cells High Supported Q9UHR5 29115 +ENSG00000161526 SAP30BP lung macrophages High Supported Q9UHR5 29115 +ENSG00000161526 SAP30BP lung pneumocytes High Supported Q9UHR5 29115 +ENSG00000161547 SRSF2 bronchus respiratory epithelial cells High Supported Q01130 6427 +ENSG00000161547 SRSF2 lung macrophages High Supported Q01130 6427 +ENSG00000161547 SRSF2 lung pneumocytes High Supported Q01130 6427 +ENSG00000161609 CCDC155 bronchus respiratory epithelial cells Medium Enhanced Q8N6L0 147872 +ENSG00000161609 CCDC155 lung macrophages Medium Enhanced Q8N6L0 147872 +ENSG00000161798 AQP5 bronchus respiratory epithelial cells Medium Enhanced P55064 362 +ENSG00000161847 RAVER1 bronchus respiratory epithelial cells High Enhanced Q8IY67 125950 +ENSG00000161847 RAVER1 lung macrophages Medium Enhanced Q8IY67 125950 +ENSG00000161847 RAVER1 lung pneumocytes Medium Enhanced Q8IY67 125950 +ENSG00000161904 LEMD2 bronchus respiratory epithelial cells High Supported Q8NC56 221496 +ENSG00000161904 LEMD2 lung macrophages Medium Supported Q8NC56 221496 +ENSG00000161904 LEMD2 lung pneumocytes High Supported Q8NC56 221496 +ENSG00000161929 SCIMP lung macrophages High Enhanced Q6UWF3 388325 +ENSG00000161956 SENP3 bronchus respiratory epithelial cells Medium Supported Q9H4L4 26168 +ENSG00000161970 RPL26 bronchus respiratory epithelial cells High Supported P61254 6154 +ENSG00000161970 RPL26 lung macrophages Medium Supported P61254 6154 +ENSG00000161970 RPL26 lung pneumocytes Low Supported P61254 6154 +ENSG00000162063 CCNF lung macrophages Medium Enhanced P41002 899 +ENSG00000162066 AMDHD2 lung macrophages Low Enhanced Q9Y303 51005 +ENSG00000162129 CLPB bronchus respiratory epithelial cells Low Enhanced Q9H078 81570 +ENSG00000162129 CLPB lung macrophages Medium Enhanced Q9H078 81570 +ENSG00000162148 PPP1R32 bronchus respiratory epithelial cells High Enhanced Q7Z5V6 220004 +ENSG00000162174 ASRGL1 bronchus respiratory epithelial cells Low Enhanced Q7L266 80150 +ENSG00000162231 NXF1 bronchus respiratory epithelial cells High Supported Q9UBU9 10482 +ENSG00000162231 NXF1 lung macrophages Medium Supported Q9UBU9 10482 +ENSG00000162231 NXF1 lung pneumocytes High Supported Q9UBU9 10482 +ENSG00000162298 SYVN1 bronchus respiratory epithelial cells Medium Enhanced Q86TM6 84447 +ENSG00000162298 SYVN1 lung macrophages High Enhanced Q86TM6 84447 +ENSG00000162298 SYVN1 lung pneumocytes Low Enhanced Q86TM6 84447 +ENSG00000162300 ZFPL1 bronchus respiratory epithelial cells Medium Enhanced O95159 7542 +ENSG00000162300 ZFPL1 lung macrophages Low Enhanced O95159 7542 +ENSG00000162300 ZFPL1 lung pneumocytes Low Enhanced O95159 7542 +ENSG00000162341 TPCN2 bronchus respiratory epithelial cells Medium Enhanced Q8NHX9 219931 +ENSG00000162341 TPCN2 lung macrophages Medium Enhanced Q8NHX9 219931 +ENSG00000162366 PDZK1IP1 bronchus respiratory epithelial cells Medium Enhanced Q13113 10158 +ENSG00000162366 PDZK1IP1 lung macrophages Medium Enhanced Q13113 10158 +ENSG00000162419 GMEB1 bronchus respiratory epithelial cells High Supported Q9Y692 10691 +ENSG00000162419 GMEB1 lung macrophages Medium Supported Q9Y692 10691 +ENSG00000162419 GMEB1 lung pneumocytes Medium Supported Q9Y692 10691 +ENSG00000162444 RBP7 bronchus respiratory epithelial cells Medium Enhanced Q96R05 116362 +ENSG00000162444 RBP7 lung macrophages Low Enhanced Q96R05 116362 +ENSG00000162444 RBP7 lung pneumocytes Medium Enhanced Q96R05 116362 +ENSG00000162493 PDPN bronchus respiratory epithelial cells Low Enhanced Q86YL7 10630 +ENSG00000162493 PDPN lung pneumocytes Medium Enhanced Q86YL7 10630 +ENSG00000162496 DHRS3 bronchus respiratory epithelial cells High Supported O75911 9249 +ENSG00000162496 DHRS3 lung macrophages High Supported O75911 9249 +ENSG00000162496 DHRS3 lung pneumocytes Low Supported O75911 9249 +ENSG00000162521 RBBP4 bronchus respiratory epithelial cells High Enhanced Q09028 5928 +ENSG00000162521 RBBP4 lung macrophages High Enhanced Q09028 5928 +ENSG00000162521 RBBP4 lung pneumocytes High Enhanced Q09028 5928 +ENSG00000162551 ALPL bronchus respiratory epithelial cells Medium Enhanced P05186 249 +ENSG00000162551 ALPL lung macrophages Medium Enhanced P05186 249 +ENSG00000162572 SCNN1D bronchus respiratory epithelial cells Medium Enhanced P51172 6339 +ENSG00000162598 C1orf87 bronchus respiratory epithelial cells High Enhanced Q8N0U7 127795 +ENSG00000162599 NFIA bronchus respiratory epithelial cells High Enhanced Q12857 4774 +ENSG00000162599 NFIA lung macrophages Low Enhanced Q12857 4774 +ENSG00000162599 NFIA lung pneumocytes Medium Enhanced Q12857 4774 +ENSG00000162613 FUBP1 bronchus respiratory epithelial cells High Enhanced Q96AE4 8880 +ENSG00000162613 FUBP1 lung macrophages High Enhanced Q96AE4 8880 +ENSG00000162613 FUBP1 lung pneumocytes High Enhanced Q96AE4 8880 +ENSG00000162627 SNX7 bronchus respiratory epithelial cells Medium Enhanced Q9UNH6 51375 +ENSG00000162627 SNX7 lung macrophages Low Enhanced Q9UNH6 51375 +ENSG00000162643 WDR63 bronchus respiratory epithelial cells Low Enhanced Q8IWG1 126820 +ENSG00000162645 GBP2 lung macrophages Medium Supported P32456 2634 +ENSG00000162645 GBP2 lung pneumocytes High Supported P32456 2634 +ENSG00000162654 GBP4 bronchus respiratory epithelial cells Medium Enhanced Q96PP9 115361 +ENSG00000162654 GBP4 lung macrophages Medium Enhanced Q96PP9 115361 +ENSG00000162654 GBP4 lung pneumocytes Low Enhanced Q96PP9 115361 +ENSG00000162664 ZNF326 bronchus respiratory epithelial cells Medium Supported Q5BKZ1 284695 +ENSG00000162664 ZNF326 lung macrophages Low Supported Q5BKZ1 284695 +ENSG00000162735 PEX19 bronchus respiratory epithelial cells High Supported P40855 5824 +ENSG00000162735 PEX19 lung macrophages High Supported P40855 5824 +ENSG00000162735 PEX19 lung pneumocytes Medium Supported P40855 5824 +ENSG00000162775 RBM15 bronchus respiratory epithelial cells Medium Supported Q96T37 64783 +ENSG00000162775 RBM15 lung macrophages Medium Supported Q96T37 64783 +ENSG00000162779 AXDND1 bronchus respiratory epithelial cells Low Enhanced Q5T1B0 126859 +ENSG00000162814 SPATA17 bronchus respiratory epithelial cells High Enhanced Q96L03 128153 +ENSG00000162849 KIF26B bronchus respiratory epithelial cells Medium Enhanced Q2KJY2 55083 +ENSG00000162849 KIF26B lung macrophages Medium Enhanced Q2KJY2 55083 +ENSG00000162896 PIGR bronchus respiratory epithelial cells High Enhanced P01833 5284 +ENSG00000162896 PIGR lung pneumocytes Low Enhanced P01833 5284 +ENSG00000162897 FCAMR bronchus respiratory epithelial cells Low Enhanced Q8WWV6 83953 +ENSG00000162897 FCAMR lung macrophages Low Enhanced Q8WWV6 83953 +ENSG00000162910 MRPL55 bronchus respiratory epithelial cells High Supported Q7Z7F7 128308 +ENSG00000162910 MRPL55 lung macrophages High Supported Q7Z7F7 128308 +ENSG00000162910 MRPL55 lung pneumocytes Medium Supported Q7Z7F7 128308 +ENSG00000162923 WDR26 bronchus respiratory epithelial cells Low Enhanced Q9H7D7 80232 +ENSG00000162923 WDR26 lung macrophages Medium Enhanced Q9H7D7 80232 +ENSG00000162928 PEX13 bronchus respiratory epithelial cells Medium Enhanced Q92968 5194 +ENSG00000162928 PEX13 lung macrophages Medium Enhanced Q92968 5194 +ENSG00000162928 PEX13 lung pneumocytes Medium Enhanced Q92968 5194 +ENSG00000162961 DPY30 bronchus respiratory epithelial cells High Supported Q9C005 84661 +ENSG00000162961 DPY30 lung macrophages Medium Supported Q9C005 84661 +ENSG00000162961 DPY30 lung pneumocytes Medium Supported Q9C005 84661 +ENSG00000163002 NUP35 bronchus respiratory epithelial cells Medium Enhanced Q8NFH5 129401 +ENSG00000163002 NUP35 lung macrophages Low Enhanced Q8NFH5 129401 +ENSG00000163002 NUP35 lung pneumocytes Low Enhanced Q8NFH5 129401 +ENSG00000163006 CCDC138 bronchus respiratory epithelial cells Low Enhanced Q96M89 165055 +ENSG00000163006 CCDC138 lung macrophages Low Enhanced Q96M89 165055 +ENSG00000163006 CCDC138 lung pneumocytes Low Enhanced Q96M89 165055 +ENSG00000163017 ACTG2 lung macrophages Low Supported P63267 72 +ENSG00000163041 H3F3A bronchus respiratory epithelial cells High Supported B4DEB1 NA +ENSG00000163041 H3F3A lung macrophages Medium Supported B4DEB1 NA +ENSG00000163041 H3F3A lung pneumocytes High Supported B4DEB1 NA +ENSG00000163071 SPATA18 bronchus respiratory epithelial cells High Enhanced Q8TC71 132671 +ENSG00000163131 CTSS bronchus respiratory epithelial cells Medium Supported P25774 1520 +ENSG00000163131 CTSS lung macrophages High Supported P25774 1520 +ENSG00000163166 IWS1 bronchus respiratory epithelial cells Medium Enhanced Q96ST2 55677 +ENSG00000163166 IWS1 lung macrophages Medium Enhanced Q96ST2 55677 +ENSG00000163166 IWS1 lung pneumocytes Medium Enhanced Q96ST2 55677 +ENSG00000163191 S100A11 bronchus respiratory epithelial cells High Enhanced P31949 6282 +ENSG00000163191 S100A11 lung macrophages High Enhanced P31949 6282 +ENSG00000163191 S100A11 lung pneumocytes Low Enhanced P31949 6282 +ENSG00000163219 ARHGAP25 lung macrophages Medium Enhanced P42331 9938 +ENSG00000163220 S100A9 lung macrophages Medium Enhanced P06702 6280 +ENSG00000163220 S100A9 lung pneumocytes Medium Enhanced P06702 6280 +ENSG00000163320 CGGBP1 bronchus respiratory epithelial cells High Supported Q9UFW8 8545 +ENSG00000163320 CGGBP1 lung macrophages High Supported Q9UFW8 8545 +ENSG00000163320 CGGBP1 lung pneumocytes High Supported Q9UFW8 8545 +ENSG00000163331 DAPL1 bronchus respiratory epithelial cells Low Enhanced A0PJW8 92196 +ENSG00000163347 CLDN1 bronchus respiratory epithelial cells Medium Enhanced O95832 9076 +ENSG00000163348 PYGO2 bronchus respiratory epithelial cells Low Supported Q9BRQ0 90780 +ENSG00000163348 PYGO2 lung macrophages Low Supported Q9BRQ0 90780 +ENSG00000163348 PYGO2 lung pneumocytes Low Supported Q9BRQ0 90780 +ENSG00000163382 NAXE bronchus respiratory epithelial cells Low Enhanced Q8NCW5 128240 +ENSG00000163382 NAXE lung macrophages Medium Enhanced Q8NCW5 128240 +ENSG00000163399 ATP1A1 bronchus respiratory epithelial cells Medium Enhanced P05023 476 +ENSG00000163399 ATP1A1 lung pneumocytes Low Enhanced P05023 476 +ENSG00000163424 C3orf30 bronchus respiratory epithelial cells Low Enhanced Q96M34 152405 +ENSG00000163435 ELF3 bronchus respiratory epithelial cells High Enhanced P78545 1999 +ENSG00000163520 FBLN2 lung macrophages Low Enhanced P98095 2199 +ENSG00000163520 FBLN2 lung pneumocytes Low Enhanced P98095 2199 +ENSG00000163521 GLB1L bronchus respiratory epithelial cells High Enhanced Q6UWU2 79411 +ENSG00000163531 NFASC bronchus respiratory epithelial cells Low Enhanced O94856 23114 +ENSG00000163531 NFASC lung macrophages Low Enhanced O94856 23114 +ENSG00000163541 SUCLG1 bronchus respiratory epithelial cells High Enhanced P53597 8802 +ENSG00000163541 SUCLG1 lung macrophages Medium Enhanced P53597 8802 +ENSG00000163541 SUCLG1 lung pneumocytes Medium Enhanced P53597 8802 +ENSG00000163563 MNDA lung macrophages High Enhanced P41218 4332 +ENSG00000163564 PYHIN1 bronchus respiratory epithelial cells Medium Enhanced Q6K0P9 149628 +ENSG00000163564 PYHIN1 lung macrophages Low Enhanced Q6K0P9 149628 +ENSG00000163564 PYHIN1 lung pneumocytes Low Enhanced Q6K0P9 149628 +ENSG00000163565 IFI16 bronchus respiratory epithelial cells Low Enhanced Q16666 3428 +ENSG00000163565 IFI16 lung macrophages Low Enhanced Q16666 3428 +ENSG00000163624 CDS1 bronchus respiratory epithelial cells High Enhanced Q92903 1040 +ENSG00000163624 CDS1 lung macrophages Medium Enhanced Q92903 1040 +ENSG00000163626 COX18 bronchus respiratory epithelial cells Medium Enhanced Q8N8Q8 285521 +ENSG00000163626 COX18 lung macrophages Medium Enhanced Q8N8Q8 285521 +ENSG00000163626 COX18 lung pneumocytes Low Enhanced Q8N8Q8 285521 +ENSG00000163631 ALB bronchus respiratory epithelial cells Medium Supported P02768 213 +ENSG00000163631 ALB lung macrophages Medium Supported P02768 213 +ENSG00000163631 ALB lung pneumocytes Medium Supported P02768 213 +ENSG00000163694 RBM47 bronchus respiratory epithelial cells High Enhanced A0AV96 54502 +ENSG00000163694 RBM47 lung macrophages Medium Enhanced A0AV96 54502 +ENSG00000163694 RBM47 lung pneumocytes Medium Enhanced A0AV96 54502 +ENSG00000163714 U2SURP bronchus respiratory epithelial cells High Enhanced O15042 23350 +ENSG00000163714 U2SURP lung macrophages High Enhanced O15042 23350 +ENSG00000163714 U2SURP lung pneumocytes Medium Enhanced O15042 23350 +ENSG00000163814 CDCP1 bronchus respiratory epithelial cells Medium Enhanced Q9H5V8 64866 +ENSG00000163814 CDCP1 lung macrophages Medium Enhanced Q9H5V8 64866 +ENSG00000163818 LZTFL1 bronchus respiratory epithelial cells High Enhanced Q9NQ48 54585 +ENSG00000163848 ZNF148 lung macrophages Medium Supported Q9UQR1 7707 +ENSG00000163848 ZNF148 lung pneumocytes Medium Supported Q9UQR1 7707 +ENSG00000163877 SNIP1 bronchus respiratory epithelial cells Low Enhanced Q8TAD8 79753 +ENSG00000163877 SNIP1 lung macrophages Medium Enhanced Q8TAD8 79753 +ENSG00000163877 SNIP1 lung pneumocytes Low Enhanced Q8TAD8 79753 +ENSG00000163882 POLR2H bronchus respiratory epithelial cells High Enhanced P52434 5437 +ENSG00000163882 POLR2H lung macrophages Medium Enhanced P52434 5437 +ENSG00000163882 POLR2H lung pneumocytes Medium Enhanced P52434 5437 +ENSG00000163885 CFAP100 bronchus respiratory epithelial cells Low Enhanced Q494V2 348807 +ENSG00000163902 RPN1 bronchus respiratory epithelial cells Medium Enhanced P04843 6184 +ENSG00000163902 RPN1 lung macrophages Medium Enhanced P04843 6184 +ENSG00000163902 RPN1 lung pneumocytes Medium Enhanced P04843 6184 +ENSG00000163918 RFC4 bronchus respiratory epithelial cells Medium Enhanced P35249 5984 +ENSG00000163918 RFC4 lung macrophages Low Enhanced P35249 5984 +ENSG00000163918 RFC4 lung pneumocytes Low Enhanced P35249 5984 +ENSG00000163931 TKT bronchus respiratory epithelial cells High Enhanced P29401 7086 +ENSG00000163931 TKT lung macrophages Low Enhanced P29401 7086 +ENSG00000163931 TKT lung pneumocytes Low Enhanced P29401 7086 +ENSG00000163932 PRKCD bronchus respiratory epithelial cells High Enhanced Q05655 5580 +ENSG00000163932 PRKCD lung macrophages High Enhanced Q05655 5580 +ENSG00000163932 PRKCD lung pneumocytes Medium Enhanced Q05655 5580 +ENSG00000163938 GNL3 bronchus respiratory epithelial cells Medium Enhanced Q9BVP2 26354 +ENSG00000163938 GNL3 lung macrophages Medium Enhanced Q9BVP2 26354 +ENSG00000163938 GNL3 lung pneumocytes Medium Enhanced Q9BVP2 26354 +ENSG00000163950 SLBP bronchus respiratory epithelial cells Medium Enhanced Q14493 7884 +ENSG00000163950 SLBP lung macrophages Medium Enhanced Q14493 7884 +ENSG00000163950 SLBP lung pneumocytes Low Enhanced Q14493 7884 +ENSG00000163956 LRPAP1 bronchus respiratory epithelial cells Medium Enhanced P30533 4043 +ENSG00000163956 LRPAP1 lung macrophages High Enhanced P30533 4043 +ENSG00000163956 LRPAP1 lung pneumocytes Medium Enhanced P30533 4043 +ENSG00000163960 UBXN7 bronchus respiratory epithelial cells Medium Enhanced O94888 26043 +ENSG00000163960 UBXN7 lung macrophages Medium Enhanced O94888 26043 +ENSG00000163960 UBXN7 lung pneumocytes Low Enhanced O94888 26043 +ENSG00000163993 S100P bronchus respiratory epithelial cells Low Enhanced P25815 6286 +ENSG00000164022 AIMP1 bronchus respiratory epithelial cells Medium Supported Q12904 9255 +ENSG00000164022 AIMP1 lung macrophages Medium Supported Q12904 9255 +ENSG00000164022 AIMP1 lung pneumocytes Low Supported Q12904 9255 +ENSG00000164023 SGMS2 bronchus respiratory epithelial cells Medium Enhanced Q8NHU3 166929 +ENSG00000164023 SGMS2 lung pneumocytes Medium Enhanced Q8NHU3 166929 +ENSG00000164032 H2AFZ bronchus respiratory epithelial cells High Supported P0C0S5 3015 +ENSG00000164032 H2AFZ lung macrophages High Supported P0C0S5 3015 +ENSG00000164032 H2AFZ lung pneumocytes High Supported P0C0S5 3015 +ENSG00000164039 BDH2 bronchus respiratory epithelial cells Medium Enhanced Q9BUT1 56898 +ENSG00000164039 BDH2 lung macrophages Medium Enhanced Q9BUT1 56898 +ENSG00000164039 BDH2 lung pneumocytes Medium Enhanced Q9BUT1 56898 +ENSG00000164050 PLXNB1 bronchus respiratory epithelial cells Medium Enhanced O43157 5364 +ENSG00000164050 PLXNB1 lung macrophages Medium Enhanced O43157 5364 +ENSG00000164051 CCDC51 bronchus respiratory epithelial cells High Supported Q96ER9 79714 +ENSG00000164051 CCDC51 lung macrophages High Supported Q96ER9 79714 +ENSG00000164062 APEH bronchus respiratory epithelial cells Medium Enhanced P13798 327 +ENSG00000164066 INTU bronchus respiratory epithelial cells Medium Enhanced Q9ULD6 27152 +ENSG00000164066 INTU lung macrophages Low Enhanced Q9ULD6 27152 +ENSG00000164066 INTU lung pneumocytes Low Enhanced Q9ULD6 27152 +ENSG00000164078 MST1R bronchus respiratory epithelial cells Medium Enhanced Q04912 4486 +ENSG00000164078 MST1R lung macrophages High Enhanced Q04912 4486 +ENSG00000164078 MST1R lung pneumocytes Low Enhanced Q04912 4486 +ENSG00000164081 TEX264 bronchus respiratory epithelial cells Low Enhanced Q9Y6I9 51368 +ENSG00000164104 HMGB2 bronchus respiratory epithelial cells Medium Enhanced P26583 3148 +ENSG00000164104 HMGB2 lung pneumocytes Low Enhanced P26583 3148 +ENSG00000164105 SAP30 bronchus respiratory epithelial cells Low Enhanced O75446 8819 +ENSG00000164105 SAP30 lung pneumocytes Low Enhanced O75446 8819 +ENSG00000164120 HPGD bronchus respiratory epithelial cells Low Enhanced P15428 3248 +ENSG00000164120 HPGD lung macrophages Medium Enhanced P15428 3248 +ENSG00000164120 HPGD lung pneumocytes Low Enhanced P15428 3248 +ENSG00000164142 FAM160A1 bronchus respiratory epithelial cells High Enhanced Q05DH4 729830 +ENSG00000164144 ARFIP1 bronchus respiratory epithelial cells Medium Enhanced P53367 27236 +ENSG00000164144 ARFIP1 lung macrophages Low Enhanced P53367 27236 +ENSG00000164144 ARFIP1 lung pneumocytes Low Enhanced P53367 27236 +ENSG00000164171 ITGA2 bronchus respiratory epithelial cells High Enhanced P17301 3673 +ENSG00000164171 ITGA2 lung pneumocytes Medium Enhanced P17301 3673 +ENSG00000164182 NDUFAF2 bronchus respiratory epithelial cells High Supported Q8N183 91942 +ENSG00000164182 NDUFAF2 lung macrophages Medium Supported Q8N183 91942 +ENSG00000164182 NDUFAF2 lung pneumocytes Low Supported Q8N183 91942 +ENSG00000164244 PRRC1 bronchus respiratory epithelial cells High Supported Q96M27 133619 +ENSG00000164244 PRRC1 lung macrophages Medium Supported Q96M27 133619 +ENSG00000164244 PRRC1 lung pneumocytes Medium Supported Q96M27 133619 +ENSG00000164258 NDUFS4 bronchus respiratory epithelial cells High Supported O43181 4724 +ENSG00000164258 NDUFS4 lung macrophages Medium Supported O43181 4724 +ENSG00000164258 NDUFS4 lung pneumocytes Low Supported O43181 4724 +ENSG00000164294 GPX8 bronchus respiratory epithelial cells Low Enhanced Q8TED1 493869 +ENSG00000164300 SERINC5 bronchus respiratory epithelial cells High Supported Q86VE9 256987 +ENSG00000164300 SERINC5 lung macrophages Medium Supported Q86VE9 256987 +ENSG00000164300 SERINC5 lung pneumocytes Medium Supported Q86VE9 256987 +ENSG00000164305 CASP3 bronchus respiratory epithelial cells Medium Enhanced P42574 836 +ENSG00000164305 CASP3 lung macrophages Low Enhanced P42574 836 +ENSG00000164308 ERAP2 bronchus respiratory epithelial cells Low Enhanced Q6P179 64167 +ENSG00000164308 ERAP2 lung macrophages High Enhanced Q6P179 64167 +ENSG00000164308 ERAP2 lung pneumocytes Low Enhanced Q6P179 64167 +ENSG00000164342 TLR3 bronchus respiratory epithelial cells Low Enhanced O15455 7098 +ENSG00000164342 TLR3 lung macrophages Medium Enhanced O15455 7098 +ENSG00000164398 ACSL6 lung macrophages Low Enhanced Q9UKU0 23305 +ENSG00000164430 MB21D1 bronchus respiratory epithelial cells Medium Enhanced Q8N884 115004 +ENSG00000164430 MB21D1 lung macrophages Medium Enhanced Q8N884 115004 +ENSG00000164430 MB21D1 lung pneumocytes Low Enhanced Q8N884 115004 +ENSG00000164442 CITED2 bronchus respiratory epithelial cells High Supported Q99967 10370 +ENSG00000164442 CITED2 lung macrophages High Supported Q99967 10370 +ENSG00000164442 CITED2 lung pneumocytes High Supported Q99967 10370 +ENSG00000164506 STXBP5 bronchus respiratory epithelial cells Medium Enhanced Q5T5C0 134957 +ENSG00000164506 STXBP5 lung pneumocytes Low Enhanced Q5T5C0 134957 +ENSG00000164508 HIST1H2AA bronchus respiratory epithelial cells Medium Supported Q96QV6 221613 +ENSG00000164508 HIST1H2AA lung macrophages High Supported Q96QV6 221613 +ENSG00000164508 HIST1H2AA lung pneumocytes High Supported Q96QV6 221613 +ENSG00000164611 PTTG1 bronchus respiratory epithelial cells Medium Enhanced O95997 9232 +ENSG00000164627 KIF6 bronchus respiratory epithelial cells Medium Enhanced Q6ZMV9 221458 +ENSG00000164687 FABP5 lung macrophages High Enhanced Q01469 2171 +ENSG00000164687 FABP5 lung pneumocytes Low Enhanced Q01469 2171 +ENSG00000164695 CHMP4C bronchus respiratory epithelial cells Medium Enhanced Q96CF2 92421 +ENSG00000164695 CHMP4C lung macrophages Medium Enhanced Q96CF2 92421 +ENSG00000164695 CHMP4C lung pneumocytes Low Enhanced Q96CF2 92421 +ENSG00000164736 SOX17 bronchus respiratory epithelial cells Medium Enhanced Q9H6I2 64321 +ENSG00000164746 C7orf57 bronchus respiratory epithelial cells High Enhanced Q8NEG2 136288 +ENSG00000164754 RAD21 bronchus respiratory epithelial cells High Supported O60216 5885 +ENSG00000164754 RAD21 lung macrophages High Supported O60216 5885 +ENSG00000164754 RAD21 lung pneumocytes High Supported O60216 5885 +ENSG00000164828 SUN1 bronchus respiratory epithelial cells High Enhanced O94901 23353 +ENSG00000164828 SUN1 lung macrophages High Enhanced O94901 23353 +ENSG00000164828 SUN1 lung pneumocytes High Enhanced O94901 23353 +ENSG00000164830 OXR1 bronchus respiratory epithelial cells Medium Enhanced Q8N573 55074 +ENSG00000164830 OXR1 lung macrophages Medium Enhanced Q8N573 55074 +ENSG00000164830 OXR1 lung pneumocytes Low Enhanced Q8N573 55074 +ENSG00000164877 MICALL2 bronchus respiratory epithelial cells Low Enhanced Q8IY33 79778 +ENSG00000164877 MICALL2 lung macrophages Low Enhanced Q8IY33 79778 +ENSG00000164885 CDK5 bronchus respiratory epithelial cells Medium Enhanced Q00535 1020 +ENSG00000164885 CDK5 lung macrophages Medium Enhanced Q00535 1020 +ENSG00000164885 CDK5 lung pneumocytes Low Enhanced Q00535 1020 +ENSG00000164889 SLC4A2 bronchus respiratory epithelial cells High Enhanced P04920 6522 +ENSG00000164889 SLC4A2 lung macrophages Medium Enhanced P04920 6522 +ENSG00000164889 SLC4A2 lung pneumocytes Low Enhanced P04920 6522 +ENSG00000164902 PHAX bronchus respiratory epithelial cells Medium Enhanced Q9H814 51808 +ENSG00000164902 PHAX lung macrophages Medium Enhanced Q9H814 51808 +ENSG00000164902 PHAX lung pneumocytes Medium Enhanced Q9H814 51808 +ENSG00000164904 ALDH7A1 bronchus respiratory epithelial cells Low Enhanced P49419 501 +ENSG00000164916 FOXK1 bronchus respiratory epithelial cells High Enhanced P85037 221937 +ENSG00000164916 FOXK1 lung macrophages Medium Enhanced P85037 221937 +ENSG00000164916 FOXK1 lung pneumocytes High Enhanced P85037 221937 +ENSG00000164919 COX6C bronchus respiratory epithelial cells High Enhanced P09669 1345 +ENSG00000164919 COX6C lung macrophages Medium Enhanced P09669 1345 +ENSG00000164919 COX6C lung pneumocytes High Enhanced P09669 1345 +ENSG00000164961 WASHC5 bronchus respiratory epithelial cells Medium Enhanced Q12768 9897 +ENSG00000164961 WASHC5 lung macrophages Medium Enhanced Q12768 9897 +ENSG00000164961 WASHC5 lung pneumocytes Medium Enhanced Q12768 9897 +ENSG00000164972 C9orf24 lung macrophages Low Enhanced Q8NCR6 84688 +ENSG00000164985 PSIP1 bronchus respiratory epithelial cells Medium Enhanced O75475 11168 +ENSG00000164985 PSIP1 lung macrophages Medium Enhanced O75475 11168 +ENSG00000164985 PSIP1 lung pneumocytes Medium Enhanced O75475 11168 +ENSG00000165025 SYK bronchus respiratory epithelial cells Low Enhanced P43405 6850 +ENSG00000165025 SYK lung macrophages High Enhanced P43405 6850 +ENSG00000165060 FXN bronchus respiratory epithelial cells Medium Supported Q16595 2395 +ENSG00000165060 FXN lung macrophages Low Supported Q16595 2395 +ENSG00000165060 FXN lung pneumocytes Medium Supported Q16595 2395 +ENSG00000165119 HNRNPK bronchus respiratory epithelial cells High Supported P61978 3190 +ENSG00000165119 HNRNPK lung macrophages High Supported P61978 3190 +ENSG00000165119 HNRNPK lung pneumocytes High Supported P61978 3190 +ENSG00000165140 FBP1 lung macrophages Medium Enhanced P09467 2203 +ENSG00000165140 FBP1 lung pneumocytes Low Enhanced P09467 2203 +ENSG00000165168 CYBB bronchus respiratory epithelial cells Low Enhanced P04839 1536 +ENSG00000165185 KIAA1958 bronchus respiratory epithelial cells Medium Enhanced Q8N8K9 158405 +ENSG00000165185 KIAA1958 lung macrophages Medium Enhanced Q8N8K9 158405 +ENSG00000165185 KIAA1958 lung pneumocytes Medium Enhanced Q8N8K9 158405 +ENSG00000165215 CLDN3 bronchus respiratory epithelial cells Medium Supported O15551 1365 +ENSG00000165238 WNK2 bronchus respiratory epithelial cells Medium Enhanced Q9Y3S1 65268 +ENSG00000165238 WNK2 lung macrophages Low Enhanced Q9Y3S1 65268 +ENSG00000165238 WNK2 lung pneumocytes Low Enhanced Q9Y3S1 65268 +ENSG00000165264 NDUFB6 bronchus respiratory epithelial cells High Supported O95139 4712 +ENSG00000165264 NDUFB6 lung macrophages Medium Supported O95139 4712 +ENSG00000165264 NDUFB6 lung pneumocytes High Supported O95139 4712 +ENSG00000165271 NOL6 bronchus respiratory epithelial cells Low Supported Q9H6R4 65083 +ENSG00000165271 NOL6 lung macrophages Medium Supported Q9H6R4 65083 +ENSG00000165271 NOL6 lung pneumocytes Medium Supported Q9H6R4 65083 +ENSG00000165272 AQP3 bronchus respiratory epithelial cells High Enhanced Q92482 360 +ENSG00000165272 AQP3 lung pneumocytes Medium Enhanced Q92482 360 +ENSG00000165280 VCP bronchus respiratory epithelial cells High Supported P55072 7415 +ENSG00000165280 VCP lung macrophages High Supported P55072 7415 +ENSG00000165280 VCP lung pneumocytes High Supported P55072 7415 +ENSG00000165283 STOML2 bronchus respiratory epithelial cells High Supported Q9UJZ1 30968 +ENSG00000165283 STOML2 lung macrophages High Supported Q9UJZ1 30968 +ENSG00000165283 STOML2 lung pneumocytes Low Supported Q9UJZ1 30968 +ENSG00000165309 ARMC3 bronchus respiratory epithelial cells High Enhanced Q5W041 219681 +ENSG00000165322 ARHGAP12 bronchus respiratory epithelial cells High Enhanced Q8IWW6 94134 +ENSG00000165322 ARHGAP12 lung macrophages Low Enhanced Q8IWW6 94134 +ENSG00000165322 ARHGAP12 lung pneumocytes Low Enhanced Q8IWW6 94134 +ENSG00000165383 LRRC18 bronchus respiratory epithelial cells Low Enhanced Q8N456 474354 +ENSG00000165475 CRYL1 bronchus respiratory epithelial cells Medium Enhanced Q9Y2S2 51084 +ENSG00000165475 CRYL1 lung macrophages Low Enhanced Q9Y2S2 51084 +ENSG00000165475 CRYL1 lung pneumocytes Low Enhanced Q9Y2S2 51084 +ENSG00000165495 PKNOX2 lung macrophages Low Supported Q96KN3 63876 +ENSG00000165495 PKNOX2 lung pneumocytes High Supported Q96KN3 63876 +ENSG00000165506 DNAAF2 bronchus respiratory epithelial cells Medium Enhanced Q9NVR5 55172 +ENSG00000165506 DNAAF2 lung macrophages Low Enhanced Q9NVR5 55172 +ENSG00000165506 DNAAF2 lung pneumocytes Medium Enhanced Q9NVR5 55172 +ENSG00000165568 AKR1E2 bronchus respiratory epithelial cells Low Enhanced Q96JD6 83592 +ENSG00000165630 PRPF18 bronchus respiratory epithelial cells High Supported Q99633 8559 +ENSG00000165630 PRPF18 lung macrophages Medium Supported Q99633 8559 +ENSG00000165630 PRPF18 lung pneumocytes Medium Supported Q99633 8559 +ENSG00000165637 VDAC2 bronchus respiratory epithelial cells Medium Enhanced P45880 7417 +ENSG00000165637 VDAC2 lung macrophages Medium Enhanced P45880 7417 +ENSG00000165671 NSD1 bronchus respiratory epithelial cells High Supported Q96L73 64324 +ENSG00000165671 NSD1 lung macrophages Medium Supported Q96L73 64324 +ENSG00000165671 NSD1 lung pneumocytes High Supported Q96L73 64324 +ENSG00000165672 PRDX3 bronchus respiratory epithelial cells High Enhanced P30048 10935 +ENSG00000165672 PRDX3 lung macrophages High Enhanced P30048 10935 +ENSG00000165672 PRDX3 lung pneumocytes Medium Enhanced P30048 10935 +ENSG00000165688 PMPCA bronchus respiratory epithelial cells High Enhanced Q10713 23203 +ENSG00000165688 PMPCA lung macrophages Medium Enhanced Q10713 23203 +ENSG00000165688 PMPCA lung pneumocytes Low Enhanced Q10713 23203 +ENSG00000165695 AK8 bronchus respiratory epithelial cells Medium Enhanced Q96MA6 158067 +ENSG00000165695 AK8 lung macrophages Medium Enhanced Q96MA6 158067 +ENSG00000165698 SPACA9 bronchus respiratory epithelial cells High Enhanced Q96E40 11092 +ENSG00000165699 TSC1 bronchus respiratory epithelial cells Medium Supported Q92574 7248 +ENSG00000165699 TSC1 lung macrophages Medium Supported Q92574 7248 +ENSG00000165699 TSC1 lung pneumocytes Medium Supported Q92574 7248 +ENSG00000165704 HPRT1 bronchus respiratory epithelial cells High Enhanced P00492 3251 +ENSG00000165704 HPRT1 lung macrophages Low Enhanced P00492 3251 +ENSG00000165724 ZMYND19 bronchus respiratory epithelial cells Medium Supported Q96E35 116225 +ENSG00000165724 ZMYND19 lung macrophages Medium Supported Q96E35 116225 +ENSG00000165724 ZMYND19 lung pneumocytes Low Supported Q96E35 116225 +ENSG00000165732 DDX21 bronchus respiratory epithelial cells Medium Enhanced Q9NR30 9188 +ENSG00000165732 DDX21 lung macrophages Low Enhanced Q9NR30 9188 +ENSG00000165732 DDX21 lung pneumocytes Low Enhanced Q9NR30 9188 +ENSG00000165757 KIAA1462 bronchus respiratory epithelial cells Medium Enhanced Q9P266 57608 +ENSG00000165757 KIAA1462 lung macrophages Low Enhanced Q9P266 57608 +ENSG00000165757 KIAA1462 lung pneumocytes Low Enhanced Q9P266 57608 +ENSG00000165795 NDRG2 bronchus respiratory epithelial cells Medium Enhanced Q9UN36 57447 +ENSG00000165795 NDRG2 lung macrophages Medium Enhanced Q9UN36 57447 +ENSG00000165795 NDRG2 lung pneumocytes Low Enhanced Q9UN36 57447 +ENSG00000165802 NSMF bronchus respiratory epithelial cells Medium Enhanced Q6X4W1 26012 +ENSG00000165802 NSMF lung macrophages High Enhanced Q6X4W1 26012 +ENSG00000165802 NSMF lung pneumocytes High Enhanced Q6X4W1 26012 +ENSG00000165807 PPP1R36 bronchus respiratory epithelial cells Low Enhanced Q96LQ0 145376 +ENSG00000165895 ARHGAP42 bronchus respiratory epithelial cells Medium Enhanced A6NI28 143872 +ENSG00000165895 ARHGAP42 lung macrophages Medium Enhanced A6NI28 143872 +ENSG00000165895 ARHGAP42 lung pneumocytes Medium Enhanced A6NI28 143872 +ENSG00000165914 TTC7B lung macrophages Low Enhanced Q86TV6 145567 +ENSG00000165934 CPSF2 bronchus respiratory epithelial cells High Supported Q9P2I0 53981 +ENSG00000165934 CPSF2 lung macrophages Medium Supported Q9P2I0 53981 +ENSG00000165934 CPSF2 lung pneumocytes High Supported Q9P2I0 53981 +ENSG00000165959 CLMN bronchus respiratory epithelial cells High Enhanced Q96JQ2 79789 +ENSG00000166033 HTRA1 bronchus respiratory epithelial cells Medium Enhanced Q92743 5654 +ENSG00000166130 IKBIP bronchus respiratory epithelial cells Low Enhanced Q70UQ0 121457 +ENSG00000166130 IKBIP lung macrophages Low Enhanced Q70UQ0 121457 +ENSG00000166135 HIF1AN bronchus respiratory epithelial cells Medium Enhanced Q9NWT6 55662 +ENSG00000166135 HIF1AN lung macrophages Medium Enhanced Q9NWT6 55662 +ENSG00000166135 HIF1AN lung pneumocytes Medium Enhanced Q9NWT6 55662 +ENSG00000166136 NDUFB8 bronchus respiratory epithelial cells Medium Supported O95169 4714 +ENSG00000166136 NDUFB8 lung pneumocytes High Supported O95169 4714 +ENSG00000166164 BRD7 bronchus respiratory epithelial cells High Enhanced Q9NPI1 29117 +ENSG00000166164 BRD7 lung macrophages Medium Enhanced Q9NPI1 29117 +ENSG00000166164 BRD7 lung pneumocytes High Enhanced Q9NPI1 29117 +ENSG00000166171 DPCD bronchus respiratory epithelial cells Medium Enhanced Q9BVM2 25911 +ENSG00000166197 NOLC1 bronchus respiratory epithelial cells Medium Supported Q14978 9221 +ENSG00000166197 NOLC1 lung pneumocytes Low Supported Q14978 9221 +ENSG00000166224 SGPL1 bronchus respiratory epithelial cells Low Enhanced O95470 8879 +ENSG00000166224 SGPL1 lung macrophages Medium Enhanced O95470 8879 +ENSG00000166224 SGPL1 lung pneumocytes Low Enhanced O95470 8879 +ENSG00000166226 CCT2 bronchus respiratory epithelial cells Low Enhanced P78371 10576 +ENSG00000166226 CCT2 lung macrophages Low Enhanced P78371 10576 +ENSG00000166226 CCT2 lung pneumocytes Medium Enhanced P78371 10576 +ENSG00000166246 C16orf71 bronchus respiratory epithelial cells Medium Enhanced Q8IYS4 146562 +ENSG00000166333 ILK bronchus respiratory epithelial cells Low Enhanced Q13418 3611 +ENSG00000166333 ILK lung macrophages Low Enhanced Q13418 3611 +ENSG00000166333 ILK lung pneumocytes Medium Enhanced Q13418 3611 +ENSG00000166337 TAF10 bronchus respiratory epithelial cells High Supported Q12962 6881 +ENSG00000166337 TAF10 lung macrophages High Supported Q12962 6881 +ENSG00000166337 TAF10 lung pneumocytes High Supported Q12962 6881 +ENSG00000166340 TPP1 bronchus respiratory epithelial cells Medium Enhanced O14773 1200 +ENSG00000166340 TPP1 lung macrophages High Enhanced O14773 1200 +ENSG00000166340 TPP1 lung pneumocytes Low Enhanced O14773 1200 +ENSG00000166347 CYB5A bronchus respiratory epithelial cells Medium Enhanced P00167 1528 +ENSG00000166347 CYB5A lung pneumocytes High Enhanced P00167 1528 +ENSG00000166394 CYB5R2 bronchus respiratory epithelial cells Low Enhanced Q6BCY4 51700 +ENSG00000166401 SERPINB8 lung macrophages Low Enhanced P50452 5271 +ENSG00000166401 SERPINB8 lung pneumocytes Medium Enhanced P50452 5271 +ENSG00000166411 IDH3A bronchus respiratory epithelial cells High Supported P50213 3419 +ENSG00000166411 IDH3A lung macrophages Medium Supported P50213 3419 +ENSG00000166411 IDH3A lung pneumocytes Medium Supported P50213 3419 +ENSG00000166432 ZMAT1 bronchus respiratory epithelial cells Medium Enhanced Q5H9K5 84460 +ENSG00000166441 RPL27A bronchus respiratory epithelial cells Medium Supported P46776 6157 +ENSG00000166441 RPL27A lung macrophages Low Supported P46776 6157 +ENSG00000166441 RPL27A lung pneumocytes Low Supported P46776 6157 +ENSG00000166477 LEO1 bronchus respiratory epithelial cells Medium Enhanced Q8WVC0 123169 +ENSG00000166477 LEO1 lung macrophages Medium Enhanced Q8WVC0 123169 +ENSG00000166477 LEO1 lung pneumocytes Low Enhanced Q8WVC0 123169 +ENSG00000166478 ZNF143 bronchus respiratory epithelial cells Medium Supported P52747 7702 +ENSG00000166478 ZNF143 lung macrophages Low Supported P52747 7702 +ENSG00000166478 ZNF143 lung pneumocytes Low Supported P52747 7702 +ENSG00000166508 MCM7 bronchus respiratory epithelial cells Low Enhanced P33993 4176 +ENSG00000166510 CCDC68 bronchus respiratory epithelial cells Medium Supported Q9H2F9 80323 +ENSG00000166510 CCDC68 lung macrophages Medium Supported Q9H2F9 80323 +ENSG00000166510 CCDC68 lung pneumocytes Medium Supported Q9H2F9 80323 +ENSG00000166526 ZNF3 bronchus respiratory epithelial cells High Supported P17036 7551 +ENSG00000166526 ZNF3 lung macrophages High Supported P17036 7551 +ENSG00000166526 ZNF3 lung pneumocytes High Supported P17036 7551 +ENSG00000166595 FAM96B bronchus respiratory epithelial cells Medium Enhanced Q9Y3D0 51647 +ENSG00000166595 FAM96B lung macrophages Medium Enhanced Q9Y3D0 51647 +ENSG00000166595 FAM96B lung pneumocytes Low Enhanced Q9Y3D0 51647 +ENSG00000166596 CFAP52 bronchus respiratory epithelial cells Medium Enhanced Q8N1V2 146845 +ENSG00000166598 HSP90B1 bronchus respiratory epithelial cells High Enhanced P14625 7184 +ENSG00000166598 HSP90B1 lung macrophages High Enhanced P14625 7184 +ENSG00000166598 HSP90B1 lung pneumocytes Medium Enhanced P14625 7184 +ENSG00000166669 ATF7IP2 bronchus respiratory epithelial cells Low Enhanced Q5U623 80063 +ENSG00000166669 ATF7IP2 lung pneumocytes Low Enhanced Q5U623 80063 +ENSG00000166685 COG1 bronchus respiratory epithelial cells High Supported Q8WTW3 9382 +ENSG00000166685 COG1 lung macrophages Low Supported Q8WTW3 9382 +ENSG00000166685 COG1 lung pneumocytes Low Supported Q8WTW3 9382 +ENSG00000166710 B2M bronchus respiratory epithelial cells High Enhanced NA NA +ENSG00000166710 B2M lung macrophages High Enhanced NA NA +ENSG00000166710 B2M lung pneumocytes High Enhanced NA NA +ENSG00000166734 CASC4 bronchus respiratory epithelial cells Medium Enhanced Q6P4E1 113201 +ENSG00000166794 PPIB bronchus respiratory epithelial cells Medium Enhanced P23284 5479 +ENSG00000166794 PPIB lung macrophages Medium Enhanced P23284 5479 +ENSG00000166816 LDHD bronchus respiratory epithelial cells High Enhanced Q86WU2 197257 +ENSG00000166816 LDHD lung macrophages Medium Enhanced Q86WU2 197257 +ENSG00000166816 LDHD lung pneumocytes Medium Enhanced Q86WU2 197257 +ENSG00000166848 TERF2IP bronchus respiratory epithelial cells Medium Supported Q9NYB0 54386 +ENSG00000166848 TERF2IP lung macrophages Low Supported Q9NYB0 54386 +ENSG00000166848 TERF2IP lung pneumocytes Medium Supported Q9NYB0 54386 +ENSG00000166902 MRPL16 bronchus respiratory epithelial cells Medium Supported Q9NX20 54948 +ENSG00000166902 MRPL16 lung macrophages High Supported Q9NX20 54948 +ENSG00000166902 MRPL16 lung pneumocytes Medium Supported Q9NX20 54948 +ENSG00000166913 YWHAB bronchus respiratory epithelial cells Medium Enhanced P31946 7529 +ENSG00000166913 YWHAB lung macrophages Medium Enhanced P31946 7529 +ENSG00000166913 YWHAB lung pneumocytes Medium Enhanced P31946 7529 +ENSG00000166920 C15orf48 bronchus respiratory epithelial cells Low Enhanced Q9C002 84419 +ENSG00000166920 C15orf48 lung macrophages Low Enhanced Q9C002 84419 +ENSG00000166946 CCNDBP1 bronchus respiratory epithelial cells High Supported O95273 23582 +ENSG00000166946 CCNDBP1 lung macrophages High Supported O95273 23582 +ENSG00000166946 CCNDBP1 lung pneumocytes High Supported O95273 23582 +ENSG00000166959 MS4A8 bronchus respiratory epithelial cells Low Enhanced Q9BY19 83661 +ENSG00000166959 MS4A8 lung macrophages Low Enhanced Q9BY19 83661 +ENSG00000166965 RCCD1 bronchus respiratory epithelial cells Medium Enhanced A6NED2 91433 +ENSG00000166965 RCCD1 lung macrophages High Enhanced A6NED2 91433 +ENSG00000166965 RCCD1 lung pneumocytes Medium Enhanced A6NED2 91433 +ENSG00000166979 EVA1C bronchus respiratory epithelial cells Medium Enhanced P58658 59271 +ENSG00000166979 EVA1C lung macrophages Low Enhanced P58658 59271 +ENSG00000166979 EVA1C lung pneumocytes Low Enhanced P58658 59271 +ENSG00000166986 MARS bronchus respiratory epithelial cells High Supported P56192 4141 +ENSG00000166986 MARS lung macrophages High Supported P56192 4141 +ENSG00000166986 MARS lung pneumocytes Medium Supported P56192 4141 +ENSG00000167004 PDIA3 bronchus respiratory epithelial cells Medium Enhanced P30101 2923 +ENSG00000167004 PDIA3 lung macrophages High Enhanced P30101 2923 +ENSG00000167004 PDIA3 lung pneumocytes Medium Enhanced P30101 2923 +ENSG00000167034 NKX3-1 bronchus respiratory epithelial cells Medium Enhanced Q99801 4824 +ENSG00000167081 PBX3 bronchus respiratory epithelial cells Medium Supported P40426 5090 +ENSG00000167081 PBX3 lung macrophages Low Supported P40426 5090 +ENSG00000167081 PBX3 lung pneumocytes Medium Supported P40426 5090 +ENSG00000167085 PHB bronchus respiratory epithelial cells High Supported P35232 5245 +ENSG00000167085 PHB lung macrophages High Supported P35232 5245 +ENSG00000167085 PHB lung pneumocytes High Supported P35232 5245 +ENSG00000167088 SNRPD1 bronchus respiratory epithelial cells Medium Supported P62314 6632 +ENSG00000167088 SNRPD1 lung macrophages Medium Supported P62314 6632 +ENSG00000167088 SNRPD1 lung pneumocytes Low Supported P62314 6632 +ENSG00000167107 ACSF2 bronchus respiratory epithelial cells Low Enhanced Q96CM8 80221 +ENSG00000167107 ACSF2 lung macrophages Low Enhanced Q96CM8 80221 +ENSG00000167110 GOLGA2 bronchus respiratory epithelial cells Medium Enhanced Q08379 2801 +ENSG00000167110 GOLGA2 lung macrophages Medium Enhanced Q08379 2801 +ENSG00000167113 COQ4 bronchus respiratory epithelial cells High Supported Q9Y3A0 51117 +ENSG00000167113 COQ4 lung macrophages High Supported Q9Y3A0 51117 +ENSG00000167113 COQ4 lung pneumocytes Medium Supported Q9Y3A0 51117 +ENSG00000167182 SP2 bronchus respiratory epithelial cells Medium Supported Q02086 6668 +ENSG00000167182 SP2 lung macrophages Medium Supported Q02086 6668 +ENSG00000167182 SP2 lung pneumocytes Medium Supported Q02086 6668 +ENSG00000167191 GPRC5B lung macrophages Medium Enhanced Q9NZH0 51704 +ENSG00000167207 NOD2 bronchus respiratory epithelial cells Medium Enhanced Q9HC29 64127 +ENSG00000167207 NOD2 lung macrophages Low Enhanced Q9HC29 64127 +ENSG00000167258 CDK12 bronchus respiratory epithelial cells High Supported Q9NYV4 51755 +ENSG00000167258 CDK12 lung macrophages High Supported Q9NYV4 51755 +ENSG00000167258 CDK12 lung pneumocytes High Supported Q9NYV4 51755 +ENSG00000167264 DUS2 bronchus respiratory epithelial cells Medium Enhanced Q9NX74 54920 +ENSG00000167264 DUS2 lung macrophages Medium Enhanced Q9NX74 54920 +ENSG00000167264 DUS2 lung pneumocytes Low Enhanced Q9NX74 54920 +ENSG00000167306 MYO5B bronchus respiratory epithelial cells High Enhanced Q9ULV0 4645 +ENSG00000167306 MYO5B lung pneumocytes Medium Enhanced Q9ULV0 4645 +ENSG00000167315 ACAA2 bronchus respiratory epithelial cells Low Enhanced P42765 10449 +ENSG00000167315 ACAA2 lung macrophages Medium Enhanced P42765 10449 +ENSG00000167315 ACAA2 lung pneumocytes Medium Enhanced P42765 10449 +ENSG00000167323 STIM1 bronchus respiratory epithelial cells Medium Enhanced Q13586 6786 +ENSG00000167323 STIM1 lung macrophages Medium Enhanced Q13586 6786 +ENSG00000167323 STIM1 lung pneumocytes Medium Enhanced Q13586 6786 +ENSG00000167325 RRM1 lung macrophages Medium Enhanced P23921 6240 +ENSG00000167378 IRGQ bronchus respiratory epithelial cells Medium Enhanced Q8WZA9 126298 +ENSG00000167468 GPX4 bronchus respiratory epithelial cells Medium Enhanced P36969 2879 +ENSG00000167491 GATAD2A bronchus respiratory epithelial cells Medium Enhanced Q86YP4 54815 +ENSG00000167491 GATAD2A lung macrophages Medium Enhanced Q86YP4 54815 +ENSG00000167491 GATAD2A lung pneumocytes Medium Enhanced Q86YP4 54815 +ENSG00000167523 SPATA33 bronchus respiratory epithelial cells High Enhanced Q96N06 124045 +ENSG00000167523 SPATA33 lung macrophages Medium Enhanced Q96N06 124045 +ENSG00000167523 SPATA33 lung pneumocytes Low Enhanced Q96N06 124045 +ENSG00000167552 TUBA1A bronchus respiratory epithelial cells High Enhanced Q71U36 7846 +ENSG00000167552 TUBA1A lung macrophages High Enhanced Q71U36 7846 +ENSG00000167552 TUBA1A lung pneumocytes High Enhanced Q71U36 7846 +ENSG00000167553 TUBA1C bronchus respiratory epithelial cells High Supported Q9BQE3 84790 +ENSG00000167553 TUBA1C lung macrophages High Supported Q9BQE3 84790 +ENSG00000167553 TUBA1C lung pneumocytes High Supported Q9BQE3 84790 +ENSG00000167554 ZNF610 bronchus respiratory epithelial cells Medium Enhanced Q8N9Z0 162963 +ENSG00000167554 ZNF610 lung macrophages Medium Enhanced Q8N9Z0 162963 +ENSG00000167554 ZNF610 lung pneumocytes Low Enhanced Q8N9Z0 162963 +ENSG00000167588 GPD1 bronchus respiratory epithelial cells Medium Enhanced P21695 2819 +ENSG00000167588 GPD1 lung macrophages High Enhanced P21695 2819 +ENSG00000167588 GPD1 lung pneumocytes Medium Enhanced P21695 2819 +ENSG00000167613 LAIR1 lung macrophages Medium Enhanced D3YTC8 3903 +ENSG00000167635 ZNF146 bronchus respiratory epithelial cells High Supported Q15072 7705 +ENSG00000167635 ZNF146 lung macrophages High Supported Q15072 7705 +ENSG00000167635 ZNF146 lung pneumocytes High Supported Q15072 7705 +ENSG00000167641 PPP1R14A bronchus respiratory epithelial cells Low Enhanced Q96A00 94274 +ENSG00000167641 PPP1R14A lung macrophages Low Enhanced Q96A00 94274 +ENSG00000167641 PPP1R14A lung pneumocytes Low Enhanced Q96A00 94274 +ENSG00000167658 EEF2 bronchus respiratory epithelial cells High Enhanced P13639 1938 +ENSG00000167658 EEF2 lung macrophages High Enhanced P13639 1938 +ENSG00000167658 EEF2 lung pneumocytes High Enhanced P13639 1938 +ENSG00000167670 CHAF1A bronchus respiratory epithelial cells Low Enhanced Q13111 10036 +ENSG00000167670 CHAF1A lung macrophages Medium Enhanced Q13111 10036 +ENSG00000167674 CTB-50L17.10 bronchus respiratory epithelial cells High Enhanced Q7Z4V5 84717 +ENSG00000167674 CTB-50L17.10 lung macrophages Medium Enhanced Q7Z4V5 84717 +ENSG00000167674 CTB-50L17.10 lung pneumocytes High Enhanced Q7Z4V5 84717 +ENSG00000167680 SEMA6B bronchus respiratory epithelial cells Low Enhanced Q9H3T3 10501 +ENSG00000167699 GLOD4 bronchus respiratory epithelial cells High Enhanced Q9HC38 51031 +ENSG00000167699 GLOD4 lung macrophages Medium Enhanced Q9HC38 51031 +ENSG00000167699 GLOD4 lung pneumocytes Medium Enhanced Q9HC38 51031 +ENSG00000167701 GPT bronchus respiratory epithelial cells Low Enhanced P24298 2875 +ENSG00000167701 GPT lung macrophages Low Enhanced P24298 2875 +ENSG00000167701 GPT lung pneumocytes Low Enhanced P24298 2875 +ENSG00000167703 SLC43A2 lung macrophages Low Enhanced NA NA +ENSG00000167778 SPRYD3 bronchus respiratory epithelial cells Medium Enhanced Q8NCJ5 84926 +ENSG00000167778 SPRYD3 lung macrophages High Enhanced Q8NCJ5 84926 +ENSG00000167778 SPRYD3 lung pneumocytes Medium Enhanced Q8NCJ5 84926 +ENSG00000167799 NUDT8 bronchus respiratory epithelial cells Medium Enhanced Q8WV74 254552 +ENSG00000167799 NUDT8 lung macrophages Medium Enhanced Q8WV74 254552 +ENSG00000167799 NUDT8 lung pneumocytes Medium Enhanced Q8WV74 254552 +ENSG00000167863 ATP5H bronchus respiratory epithelial cells Medium Enhanced O75947 10476 +ENSG00000167863 ATP5H lung macrophages Medium Enhanced O75947 10476 +ENSG00000167863 ATP5H lung pneumocytes Medium Enhanced O75947 10476 +ENSG00000167880 EVPL bronchus respiratory epithelial cells Medium Enhanced Q92817 2125 +ENSG00000167880 EVPL lung macrophages Medium Enhanced Q92817 2125 +ENSG00000167900 TK1 bronchus respiratory epithelial cells Medium Enhanced P04183 7083 +ENSG00000167900 TK1 lung macrophages Low Enhanced P04183 7083 +ENSG00000167969 ECI1 bronchus respiratory epithelial cells High Enhanced P42126 1632 +ENSG00000167969 ECI1 lung macrophages Medium Enhanced P42126 1632 +ENSG00000167969 ECI1 lung pneumocytes Medium Enhanced P42126 1632 +ENSG00000167972 ABCA3 bronchus respiratory epithelial cells Medium Enhanced Q99758 21 +ENSG00000167972 ABCA3 lung macrophages Medium Enhanced Q99758 21 +ENSG00000167972 ABCA3 lung pneumocytes High Enhanced Q99758 21 +ENSG00000167978 SRRM2 bronchus respiratory epithelial cells High Supported Q9UQ35 23524 +ENSG00000167978 SRRM2 lung macrophages High Supported Q9UQ35 23524 +ENSG00000167978 SRRM2 lung pneumocytes High Supported Q9UQ35 23524 +ENSG00000167985 SDHAF2 bronchus respiratory epithelial cells High Supported Q9NX18 54949 +ENSG00000167985 SDHAF2 lung macrophages Medium Supported Q9NX18 54949 +ENSG00000167985 SDHAF2 lung pneumocytes Low Supported Q9NX18 54949 +ENSG00000168036 CTNNB1 bronchus respiratory epithelial cells High Enhanced P35222 1499 +ENSG00000168036 CTNNB1 lung macrophages Medium Enhanced P35222 1499 +ENSG00000168036 CTNNB1 lung pneumocytes Medium Enhanced P35222 1499 +ENSG00000168040 FADD bronchus respiratory epithelial cells Low Supported Q13158 8772 +ENSG00000168040 FADD lung macrophages Low Supported Q13158 8772 +ENSG00000168060 NAALADL1 lung macrophages Low Enhanced Q9UQQ1 10004 +ENSG00000168060 NAALADL1 lung pneumocytes Low Enhanced Q9UQQ1 10004 +ENSG00000168066 SF1 bronchus respiratory epithelial cells High Supported Q15637 7536 +ENSG00000168066 SF1 lung macrophages High Supported Q15637 7536 +ENSG00000168066 SF1 lung pneumocytes High Supported Q15637 7536 +ENSG00000168067 MAP4K2 bronchus respiratory epithelial cells Medium Enhanced Q12851 5871 +ENSG00000168067 MAP4K2 lung macrophages High Enhanced Q12851 5871 +ENSG00000168067 MAP4K2 lung pneumocytes Low Enhanced Q12851 5871 +ENSG00000168116 KIAA1586 bronchus respiratory epithelial cells Medium Enhanced Q9HCI6 57691 +ENSG00000168148 HIST3H3 bronchus respiratory epithelial cells High Supported Q16695 8290 +ENSG00000168148 HIST3H3 lung macrophages High Supported Q16695 8290 +ENSG00000168148 HIST3H3 lung pneumocytes High Supported Q16695 8290 +ENSG00000168269 FOXI1 bronchus respiratory epithelial cells Low Enhanced Q12951 2299 +ENSG00000168280 KIF5C bronchus respiratory epithelial cells Low Enhanced O60282 3800 +ENSG00000168280 KIF5C lung pneumocytes Medium Enhanced O60282 3800 +ENSG00000168283 BMI1 bronchus respiratory epithelial cells High Supported P35226 100532731; 648 +ENSG00000168283 BMI1 lung macrophages Low Supported P35226 100532731; 648 +ENSG00000168283 BMI1 lung pneumocytes Medium Supported P35226 100532731; 648 +ENSG00000168286 THAP11 bronchus respiratory epithelial cells Medium Supported Q96EK4 57215 +ENSG00000168286 THAP11 lung macrophages Medium Supported Q96EK4 57215 +ENSG00000168286 THAP11 lung pneumocytes Medium Supported Q96EK4 57215 +ENSG00000168288 MMADHC bronchus respiratory epithelial cells Medium Supported Q9H3L0 27249 +ENSG00000168288 MMADHC lung macrophages Medium Supported Q9H3L0 27249 +ENSG00000168291 PDHB bronchus respiratory epithelial cells Low Enhanced P11177 5162 +ENSG00000168291 PDHB lung macrophages Low Enhanced P11177 5162 +ENSG00000168297 PXK bronchus respiratory epithelial cells Medium Supported Q7Z7A4 54899 +ENSG00000168297 PXK lung macrophages Medium Supported Q7Z7A4 54899 +ENSG00000168297 PXK lung pneumocytes Low Supported Q7Z7A4 54899 +ENSG00000168298 HIST1H1E bronchus respiratory epithelial cells High Supported P10412 3008 +ENSG00000168298 HIST1H1E lung macrophages Medium Supported P10412 3008 +ENSG00000168298 HIST1H1E lung pneumocytes High Supported P10412 3008 +ENSG00000168306 ACOX2 bronchus respiratory epithelial cells Medium Enhanced Q99424 8309 +ENSG00000168306 ACOX2 lung macrophages Low Enhanced Q99424 8309 +ENSG00000168310 IRF2 bronchus respiratory epithelial cells Medium Supported P14316 3660 +ENSG00000168310 IRF2 lung macrophages Low Supported P14316 3660 +ENSG00000168310 IRF2 lung pneumocytes Low Supported P14316 3660 +ENSG00000168385 SEPT2 bronchus respiratory epithelial cells Medium Supported Q15019 4735 +ENSG00000168385 SEPT2 lung macrophages Low Supported Q15019 4735 +ENSG00000168385 SEPT2 lung pneumocytes Medium Supported Q15019 4735 +ENSG00000168439 STIP1 bronchus respiratory epithelial cells Low Enhanced P31948 10963 +ENSG00000168439 STIP1 lung macrophages Low Enhanced P31948 10963 +ENSG00000168439 STIP1 lung pneumocytes Low Enhanced P31948 10963 +ENSG00000168454 TXNDC2 bronchus respiratory epithelial cells Low Enhanced Q86VQ3 84203 +ENSG00000168454 TXNDC2 lung macrophages Low Enhanced Q86VQ3 84203 +ENSG00000168484 SFTPC lung pneumocytes High Enhanced P11686 6440 +ENSG00000168487 BMP1 bronchus respiratory epithelial cells Low Enhanced P13497 649 +ENSG00000168487 BMP1 lung macrophages Medium Enhanced P13497 649 +ENSG00000168495 POLR3D bronchus respiratory epithelial cells Medium Enhanced P05423 661 +ENSG00000168495 POLR3D lung macrophages Low Enhanced P05423 661 +ENSG00000168496 FEN1 bronchus respiratory epithelial cells Low Enhanced P39748 2237 +ENSG00000168496 FEN1 lung macrophages High Enhanced P39748 2237 +ENSG00000168496 FEN1 lung pneumocytes Low Enhanced P39748 2237 +ENSG00000168497 SDPR bronchus respiratory epithelial cells Low Enhanced O95810 8436 +ENSG00000168497 SDPR lung pneumocytes Medium Enhanced O95810 8436 +ENSG00000168517 HEXIM2 bronchus respiratory epithelial cells Medium Enhanced Q96MH2 124790 +ENSG00000168517 HEXIM2 lung macrophages Medium Enhanced Q96MH2 124790 +ENSG00000168517 HEXIM2 lung pneumocytes Medium Enhanced Q96MH2 124790 +ENSG00000168528 SERINC2 bronchus respiratory epithelial cells High Enhanced Q96SA4 347735 +ENSG00000168528 SERINC2 lung macrophages High Enhanced Q96SA4 347735 +ENSG00000168556 ING2 bronchus respiratory epithelial cells High Enhanced Q9H160 3622 +ENSG00000168556 ING2 lung macrophages Medium Enhanced Q9H160 3622 +ENSG00000168556 ING2 lung pneumocytes Medium Enhanced Q9H160 3622 +ENSG00000168610 STAT3 bronchus respiratory epithelial cells Medium Supported P40763 6774 +ENSG00000168610 STAT3 lung pneumocytes Medium Supported P40763 6774 +ENSG00000168653 NDUFS5 bronchus respiratory epithelial cells Medium Supported O43920 4725 +ENSG00000168653 NDUFS5 lung macrophages Low Supported O43920 4725 +ENSG00000168653 NDUFS5 lung pneumocytes Low Supported O43920 4725 +ENSG00000168701 TMEM208 bronchus respiratory epithelial cells Medium Supported Q9BTX3 29100 +ENSG00000168701 TMEM208 lung macrophages Medium Supported Q9BTX3 29100 +ENSG00000168701 TMEM208 lung pneumocytes Low Supported Q9BTX3 29100 +ENSG00000168743 NPNT lung pneumocytes High Supported Q6UXI9 255743 +ENSG00000168763 CNNM3 bronchus respiratory epithelial cells High Supported Q8NE01 26505 +ENSG00000168763 CNNM3 lung macrophages Medium Supported Q8NE01 26505 +ENSG00000168763 CNNM3 lung pneumocytes Low Supported Q8NE01 26505 +ENSG00000168769 TET2 bronchus respiratory epithelial cells High Supported Q6N021 54790 +ENSG00000168769 TET2 lung macrophages Medium Supported Q6N021 54790 +ENSG00000168769 TET2 lung pneumocytes Medium Supported Q6N021 54790 +ENSG00000168778 TCTN2 bronchus respiratory epithelial cells High Enhanced Q96GX1 79867 +ENSG00000168778 TCTN2 lung macrophages Medium Enhanced Q96GX1 79867 +ENSG00000168827 GFM1 bronchus respiratory epithelial cells High Enhanced Q96RP9 85476 +ENSG00000168827 GFM1 lung macrophages High Enhanced Q96RP9 85476 +ENSG00000168878 SFTPB lung pneumocytes Medium Enhanced P07988 6439 +ENSG00000168884 TNIP2 bronchus respiratory epithelial cells High Supported Q8NFZ5 79155 +ENSG00000168884 TNIP2 lung macrophages High Supported Q8NFZ5 79155 +ENSG00000168884 TNIP2 lung pneumocytes High Supported Q8NFZ5 79155 +ENSG00000168899 VAMP5 bronchus respiratory epithelial cells Medium Supported O95183 10791 +ENSG00000168899 VAMP5 lung pneumocytes Medium Supported O95183 10791 +ENSG00000168907 PLA2G4F bronchus respiratory epithelial cells Low Enhanced Q68DD2 255189 +ENSG00000168907 PLA2G4F lung macrophages Low Enhanced Q68DD2 255189 +ENSG00000168924 LETM1 bronchus respiratory epithelial cells High Enhanced O95202 3954 +ENSG00000168924 LETM1 lung macrophages Medium Enhanced O95202 3954 +ENSG00000168924 LETM1 lung pneumocytes Low Enhanced O95202 3954 +ENSG00000169020 ATP5I bronchus respiratory epithelial cells High Supported P56385 521 +ENSG00000169020 ATP5I lung macrophages High Supported P56385 521 +ENSG00000169020 ATP5I lung pneumocytes Medium Supported P56385 521 +ENSG00000169021 UQCRFS1 bronchus respiratory epithelial cells Medium Enhanced P47985 7386 +ENSG00000169021 UQCRFS1 lung macrophages Low Enhanced P47985 7386 +ENSG00000169021 UQCRFS1 lung pneumocytes Low Enhanced P47985 7386 +ENSG00000169045 HNRNPH1 bronchus respiratory epithelial cells High Supported P31943 3187 +ENSG00000169045 HNRNPH1 lung macrophages Medium Supported P31943 3187 +ENSG00000169045 HNRNPH1 lung pneumocytes Medium Supported P31943 3187 +ENSG00000169057 MECP2 bronchus respiratory epithelial cells High Enhanced P51608 4204 +ENSG00000169057 MECP2 lung macrophages High Enhanced P51608 4204 +ENSG00000169057 MECP2 lung pneumocytes High Enhanced P51608 4204 +ENSG00000169064 ZBBX bronchus respiratory epithelial cells Medium Enhanced A8MT70 79740 +ENSG00000169093 ASMTL bronchus respiratory epithelial cells Medium Enhanced O95671 8623 +ENSG00000169093 ASMTL lung pneumocytes Low Enhanced O95671 8623 +ENSG00000169126 ARMC4 bronchus respiratory epithelial cells Low Enhanced Q5T2S8 55130 +ENSG00000169189 NSMCE1 bronchus respiratory epithelial cells Medium Enhanced Q8WV22 197370 +ENSG00000169189 NSMCE1 lung macrophages Medium Enhanced Q8WV22 197370 +ENSG00000169217 CD2BP2 bronchus respiratory epithelial cells Medium Enhanced O95400 10421 +ENSG00000169217 CD2BP2 lung macrophages Low Enhanced O95400 10421 +ENSG00000169220 RGS14 bronchus respiratory epithelial cells Low Enhanced O43566 10636 +ENSG00000169220 RGS14 lung macrophages Medium Enhanced O43566 10636 +ENSG00000169288 MRPL1 bronchus respiratory epithelial cells High Supported Q9BYD6 65008 +ENSG00000169288 MRPL1 lung macrophages High Supported Q9BYD6 65008 +ENSG00000169288 MRPL1 lung pneumocytes Medium Supported Q9BYD6 65008 +ENSG00000169375 SIN3A bronchus respiratory epithelial cells Medium Enhanced Q96ST3 25942 +ENSG00000169375 SIN3A lung pneumocytes Low Enhanced Q96ST3 25942 +ENSG00000169379 ARL13B bronchus respiratory epithelial cells Low Enhanced Q3SXY8 200894 +ENSG00000169379 ARL13B lung macrophages Medium Enhanced Q3SXY8 200894 +ENSG00000169379 ARL13B lung pneumocytes Low Enhanced Q3SXY8 200894 +ENSG00000169564 PCBP1 bronchus respiratory epithelial cells Medium Supported Q15365 5093 +ENSG00000169564 PCBP1 lung macrophages Medium Supported Q15365 5093 +ENSG00000169564 PCBP1 lung pneumocytes Medium Supported Q15365 5093 +ENSG00000169583 CLIC3 bronchus respiratory epithelial cells Medium Enhanced O95833 9022 +ENSG00000169583 CLIC3 lung pneumocytes Low Enhanced O95833 9022 +ENSG00000169612 FAM103A1 bronchus respiratory epithelial cells High Enhanced Q9BTL3 83640 +ENSG00000169612 FAM103A1 lung macrophages High Enhanced Q9BTL3 83640 +ENSG00000169612 FAM103A1 lung pneumocytes High Enhanced Q9BTL3 83640 +ENSG00000169627 BOLA2B bronchus respiratory epithelial cells Medium Supported H3BPT9 NA +ENSG00000169627 BOLA2B lung macrophages Low Supported H3BPT9 NA +ENSG00000169641 LUZP1 bronchus respiratory epithelial cells Medium Enhanced Q86V48 7798 +ENSG00000169641 LUZP1 lung pneumocytes Low Enhanced Q86V48 7798 +ENSG00000169682 SPNS1 bronchus respiratory epithelial cells Low Enhanced Q9H2V7 83985 +ENSG00000169682 SPNS1 lung macrophages High Enhanced Q9H2V7 83985 +ENSG00000169683 LRRC45 bronchus respiratory epithelial cells High Enhanced Q96CN5 201255 +ENSG00000169683 LRRC45 lung macrophages Medium Enhanced Q96CN5 201255 +ENSG00000169683 LRRC45 lung pneumocytes Low Enhanced Q96CN5 201255 +ENSG00000169738 DCXR bronchus respiratory epithelial cells Medium Enhanced Q7Z4W1 51181 +ENSG00000169738 DCXR lung macrophages Medium Enhanced Q7Z4W1 51181 +ENSG00000169744 LDB2 bronchus respiratory epithelial cells Medium Supported O43679 9079 +ENSG00000169744 LDB2 lung macrophages Low Supported O43679 9079 +ENSG00000169744 LDB2 lung pneumocytes Medium Supported O43679 9079 +ENSG00000169764 UGP2 bronchus respiratory epithelial cells Low Enhanced Q16851 7360 +ENSG00000169783 LINGO1 lung macrophages Medium Enhanced Q96FE5 84894 +ENSG00000169813 HNRNPF bronchus respiratory epithelial cells High Supported P52597 3185 +ENSG00000169813 HNRNPF lung macrophages Medium Supported P52597 3185 +ENSG00000169813 HNRNPF lung pneumocytes Medium Supported P52597 3185 +ENSG00000169860 P2RY1 bronchus respiratory epithelial cells Medium Enhanced P47900 5028 +ENSG00000169860 P2RY1 lung macrophages Medium Enhanced P47900 5028 +ENSG00000169884 WNT10B bronchus respiratory epithelial cells Medium Enhanced O00744 7480 +ENSG00000169896 ITGAM lung macrophages Low Enhanced P11215 3684 +ENSG00000169957 ZNF768 bronchus respiratory epithelial cells High Supported Q9H5H4 79724 +ENSG00000169957 ZNF768 lung pneumocytes Medium Supported Q9H5H4 79724 +ENSG00000170004 CHD3 bronchus respiratory epithelial cells Medium Supported Q12873 1107 +ENSG00000170004 CHD3 lung macrophages Medium Supported Q12873 1107 +ENSG00000170004 CHD3 lung pneumocytes Low Supported Q12873 1107 +ENSG00000170088 TMEM192 bronchus respiratory epithelial cells Medium Enhanced Q8IY95 201931 +ENSG00000170088 TMEM192 lung macrophages Medium Enhanced Q8IY95 201931 +ENSG00000170088 TMEM192 lung pneumocytes Medium Enhanced Q8IY95 201931 +ENSG00000170144 HNRNPA3 bronchus respiratory epithelial cells High Supported P51991 220988 +ENSG00000170144 HNRNPA3 lung macrophages Medium Supported P51991 220988 +ENSG00000170144 HNRNPA3 lung pneumocytes High Supported P51991 220988 +ENSG00000170242 USP47 bronchus respiratory epithelial cells High Supported Q96K76 55031 +ENSG00000170242 USP47 lung macrophages High Supported Q96K76 55031 +ENSG00000170242 USP47 lung pneumocytes Medium Supported Q96K76 55031 +ENSG00000170264 FAM161A bronchus respiratory epithelial cells High Enhanced Q3B820 84140 +ENSG00000170264 FAM161A lung pneumocytes Low Enhanced Q3B820 84140 +ENSG00000170265 ZNF282 bronchus respiratory epithelial cells High Supported Q9UDV7 8427 +ENSG00000170265 ZNF282 lung macrophages Low Supported Q9UDV7 8427 +ENSG00000170265 ZNF282 lung pneumocytes Low Supported Q9UDV7 8427 +ENSG00000170266 GLB1 bronchus respiratory epithelial cells Medium Enhanced P16278 2720 +ENSG00000170266 GLB1 lung macrophages High Enhanced P16278 2720 +ENSG00000170266 GLB1 lung pneumocytes Low Enhanced P16278 2720 +ENSG00000170312 CDK1 lung macrophages Low Enhanced P06493 983 +ENSG00000170315 UBB bronchus respiratory epithelial cells High Supported P0CG47 7314 +ENSG00000170315 UBB lung macrophages Medium Supported P0CG47 7314 +ENSG00000170315 UBB lung pneumocytes Medium Supported P0CG47 7314 +ENSG00000170348 TMED10 bronchus respiratory epithelial cells Medium Enhanced P49755 10972 +ENSG00000170348 TMED10 lung macrophages Medium Enhanced P49755 10972 +ENSG00000170348 TMED10 lung pneumocytes Medium Enhanced P49755 10972 +ENSG00000170412 GPRC5C bronchus respiratory epithelial cells Low Enhanced Q9NQ84 55890 +ENSG00000170412 GPRC5C lung macrophages Medium Enhanced Q9NQ84 55890 +ENSG00000170421 KRT8 bronchus respiratory epithelial cells High Enhanced P05787 3856 +ENSG00000170421 KRT8 lung pneumocytes Medium Enhanced P05787 3856 +ENSG00000170430 MGMT bronchus respiratory epithelial cells High Supported P16455 4255 +ENSG00000170430 MGMT lung macrophages High Supported P16455 4255 +ENSG00000170430 MGMT lung pneumocytes High Supported P16455 4255 +ENSG00000170439 METTL7B lung pneumocytes Medium Enhanced Q6UX53 196410 +ENSG00000170458 CD14 lung macrophages Medium Enhanced P08571 929 +ENSG00000170465 KRT6C bronchus respiratory epithelial cells Medium Supported P48668 286887 +ENSG00000170473 PYM1 bronchus respiratory epithelial cells High Supported Q9BRP8 84305 +ENSG00000170473 PYM1 lung macrophages Medium Supported Q9BRP8 84305 +ENSG00000170473 PYM1 lung pneumocytes Medium Supported Q9BRP8 84305 +ENSG00000170477 KRT4 bronchus respiratory epithelial cells Low Supported P19013 NA +ENSG00000170515 PA2G4 bronchus respiratory epithelial cells High Supported Q9UQ80 5036 +ENSG00000170515 PA2G4 lung macrophages High Supported Q9UQ80 5036 +ENSG00000170515 PA2G4 lung pneumocytes Medium Supported Q9UQ80 5036 +ENSG00000170545 SMAGP bronchus respiratory epithelial cells Medium Enhanced Q0VAQ4 57228 +ENSG00000170545 SMAGP lung macrophages Medium Enhanced Q0VAQ4 57228 +ENSG00000170545 SMAGP lung pneumocytes Low Enhanced Q0VAQ4 57228 +ENSG00000170632 ARMC10 bronchus respiratory epithelial cells Medium Enhanced Q8N2F6 83787 +ENSG00000170632 ARMC10 lung macrophages Medium Enhanced Q8N2F6 83787 +ENSG00000170632 ARMC10 lung pneumocytes Low Enhanced Q8N2F6 83787 +ENSG00000170703 TTLL6 bronchus respiratory epithelial cells High Enhanced Q8N841 284076 +ENSG00000170786 SDR16C5 bronchus respiratory epithelial cells High Enhanced Q8N3Y7 195814 +ENSG00000170786 SDR16C5 lung macrophages Low Enhanced Q8N3Y7 195814 +ENSG00000170786 SDR16C5 lung pneumocytes High Enhanced Q8N3Y7 195814 +ENSG00000170802 FOXN2 lung macrophages Medium Supported P32314 3344 +ENSG00000170854 RIOX2 bronchus respiratory epithelial cells High Supported Q8IUF8 84864 +ENSG00000170854 RIOX2 lung macrophages Low Supported Q8IUF8 84864 +ENSG00000170854 RIOX2 lung pneumocytes Medium Supported Q8IUF8 84864 +ENSG00000170906 NDUFA3 bronchus respiratory epithelial cells High Supported NA NA +ENSG00000170906 NDUFA3 lung macrophages Medium Supported NA NA +ENSG00000170906 NDUFA3 lung pneumocytes Low Supported NA NA +ENSG00000170989 S1PR1 bronchus respiratory epithelial cells High Supported P21453 1901 +ENSG00000170989 S1PR1 lung macrophages Low Supported P21453 1901 +ENSG00000171103 TRMT61B bronchus respiratory epithelial cells Medium Enhanced Q9BVS5 55006 +ENSG00000171103 TRMT61B lung macrophages High Enhanced Q9BVS5 55006 +ENSG00000171103 TRMT61B lung pneumocytes Medium Enhanced Q9BVS5 55006 +ENSG00000171115 GIMAP8 lung macrophages High Supported Q8ND71 155038 +ENSG00000171115 GIMAP8 lung pneumocytes High Supported Q8ND71 155038 +ENSG00000171124 FUT3 bronchus respiratory epithelial cells Low Supported P21217 2525 +ENSG00000171124 FUT3 lung macrophages Low Supported P21217 2525 +ENSG00000171174 RBKS bronchus respiratory epithelial cells Medium Enhanced Q9H477 64080 +ENSG00000171174 RBKS lung macrophages Low Enhanced Q9H477 64080 +ENSG00000171174 RBKS lung pneumocytes Low Enhanced Q9H477 64080 +ENSG00000171219 CDC42BPG bronchus respiratory epithelial cells Low Enhanced Q6DT37 55561 +ENSG00000171219 CDC42BPG lung pneumocytes Low Enhanced Q6DT37 55561 +ENSG00000171224 C10orf35 bronchus respiratory epithelial cells Medium Enhanced Q96D05 219738 +ENSG00000171227 TMEM37 bronchus respiratory epithelial cells Low Enhanced Q8WXS4 140738 +ENSG00000171236 LRG1 bronchus respiratory epithelial cells Low Enhanced P02750 116844 +ENSG00000171236 LRG1 lung pneumocytes Low Enhanced P02750 116844 +ENSG00000171262 FAM98B bronchus respiratory epithelial cells Medium Enhanced Q52LJ0 283742 +ENSG00000171262 FAM98B lung macrophages Medium Enhanced Q52LJ0 283742 +ENSG00000171262 FAM98B lung pneumocytes Low Enhanced Q52LJ0 283742 +ENSG00000171298 GAA lung macrophages High Enhanced P10253 2548 +ENSG00000171302 CANT1 bronchus respiratory epithelial cells High Enhanced Q8WVQ1 124583 +ENSG00000171302 CANT1 lung macrophages Low Enhanced Q8WVQ1 124583 +ENSG00000171345 KRT19 bronchus respiratory epithelial cells High Enhanced P08727 3880 +ENSG00000171345 KRT19 lung pneumocytes High Enhanced P08727 3880 +ENSG00000171346 KRT15 bronchus respiratory epithelial cells Medium Enhanced P19012 3866 +ENSG00000171368 TPPP bronchus respiratory epithelial cells Medium Enhanced O94811 11076 +ENSG00000171368 TPPP lung pneumocytes Low Enhanced O94811 11076 +ENSG00000171475 WIPF2 bronchus respiratory epithelial cells Medium Enhanced Q8TF74 147179 +ENSG00000171475 WIPF2 lung pneumocytes Low Enhanced Q8TF74 147179 +ENSG00000171476 HOPX lung pneumocytes Medium Enhanced Q9BPY8 84525 +ENSG00000171490 RSL1D1 bronchus respiratory epithelial cells High Supported O76021 26156 +ENSG00000171490 RSL1D1 lung macrophages Low Supported O76021 26156 +ENSG00000171503 ETFDH bronchus respiratory epithelial cells Medium Enhanced Q16134 2110 +ENSG00000171503 ETFDH lung macrophages Medium Enhanced Q16134 2110 +ENSG00000171564 FGB bronchus respiratory epithelial cells Medium Enhanced P02675 2244 +ENSG00000171564 FGB lung macrophages Medium Enhanced P02675 2244 +ENSG00000171566 PLRG1 bronchus respiratory epithelial cells High Supported O43660 5356 +ENSG00000171566 PLRG1 lung macrophages Low Supported O43660 5356 +ENSG00000171566 PLRG1 lung pneumocytes Medium Supported O43660 5356 +ENSG00000171595 DNAI2 bronchus respiratory epithelial cells Medium Enhanced Q9GZS0 64446 +ENSG00000171608 PIK3CD bronchus respiratory epithelial cells Low Enhanced O00329 5293 +ENSG00000171681 ATF7IP bronchus respiratory epithelial cells Low Enhanced Q6VMQ6 55729 +ENSG00000171681 ATF7IP lung macrophages Low Enhanced Q6VMQ6 55729 +ENSG00000171681 ATF7IP lung pneumocytes Low Enhanced Q6VMQ6 55729 +ENSG00000171700 RGS19 lung macrophages Medium Enhanced P49795 10287 +ENSG00000171720 HDAC3 bronchus respiratory epithelial cells Low Supported O15379 8841 +ENSG00000171720 HDAC3 lung macrophages Low Supported O15379 8841 +ENSG00000171720 HDAC3 lung pneumocytes Low Supported O15379 8841 +ENSG00000171723 GPHN bronchus respiratory epithelial cells Medium Enhanced Q9NQX3 10243 +ENSG00000171723 GPHN lung macrophages Medium Enhanced Q9NQX3 10243 +ENSG00000171723 GPHN lung pneumocytes Low Enhanced Q9NQX3 10243 +ENSG00000171791 BCL2 bronchus respiratory epithelial cells High Enhanced P10415 596 +ENSG00000171793 CTPS1 bronchus respiratory epithelial cells Medium Enhanced P17812 1503 +ENSG00000171793 CTPS1 lung macrophages Low Enhanced P17812 1503 +ENSG00000171793 CTPS1 lung pneumocytes Low Enhanced P17812 1503 +ENSG00000171817 ZNF540 bronchus respiratory epithelial cells High Supported Q8NDQ6 163255 +ENSG00000171817 ZNF540 lung macrophages High Supported Q8NDQ6 163255 +ENSG00000171817 ZNF540 lung pneumocytes High Supported Q8NDQ6 163255 +ENSG00000171824 EXOSC10 bronchus respiratory epithelial cells Low Enhanced Q01780 5394 +ENSG00000171860 C3AR1 bronchus respiratory epithelial cells Low Enhanced Q16581 719 +ENSG00000171860 C3AR1 lung macrophages Low Enhanced Q16581 719 +ENSG00000171860 C3AR1 lung pneumocytes Low Enhanced Q16581 719 +ENSG00000171861 MRM3 bronchus respiratory epithelial cells Medium Enhanced Q9HC36 55178 +ENSG00000171861 MRM3 lung macrophages Medium Enhanced Q9HC36 55178 +ENSG00000171867 PRNP lung macrophages Low Enhanced P04156 5621 +ENSG00000171885 AQP4 lung pneumocytes Medium Enhanced P55087 361 +ENSG00000171914 TLN2 lung macrophages Low Enhanced Q9Y4G6 83660 +ENSG00000171953 ATPAF2 bronchus respiratory epithelial cells Medium Supported Q8N5M1 91647 +ENSG00000171953 ATPAF2 lung macrophages Medium Supported Q8N5M1 91647 +ENSG00000171953 ATPAF2 lung pneumocytes Low Supported Q8N5M1 91647 +ENSG00000172037 LAMB2 lung pneumocytes Medium Supported P55268 3913 +ENSG00000172053 QARS bronchus respiratory epithelial cells Medium Enhanced P47897 5859 +ENSG00000172053 QARS lung macrophages Medium Enhanced P47897 5859 +ENSG00000172062 SMN1 bronchus respiratory epithelial cells High Enhanced NA NA +ENSG00000172062 SMN1 lung macrophages Low Enhanced NA NA +ENSG00000172062 SMN1 lung pneumocytes Low Enhanced NA NA +ENSG00000172071 EIF2AK3 bronchus respiratory epithelial cells High Enhanced Q9NZJ5 9451 +ENSG00000172071 EIF2AK3 lung macrophages Medium Enhanced Q9NZJ5 9451 +ENSG00000172071 EIF2AK3 lung pneumocytes Low Enhanced Q9NZJ5 9451 +ENSG00000172115 CYCS bronchus respiratory epithelial cells Medium Enhanced P99999 54205 +ENSG00000172115 CYCS lung macrophages Medium Enhanced P99999 54205 +ENSG00000172115 CYCS lung pneumocytes Low Enhanced P99999 54205 +ENSG00000172137 CALB2 bronchus respiratory epithelial cells Low Enhanced NA NA +ENSG00000172137 CALB2 lung macrophages Low Enhanced NA NA +ENSG00000172175 MALT1 lung macrophages Low Enhanced Q9UDY8 10892 +ENSG00000172216 CEBPB bronchus respiratory epithelial cells High Supported P17676 1051 +ENSG00000172216 CEBPB lung macrophages High Supported P17676 1051 +ENSG00000172216 CEBPB lung pneumocytes Low Supported P17676 1051 +ENSG00000172264 MACROD2 bronchus respiratory epithelial cells Medium Enhanced A1Z1Q3 140733 +ENSG00000172264 MACROD2 lung macrophages Medium Enhanced A1Z1Q3 140733 +ENSG00000172264 MACROD2 lung pneumocytes Medium Enhanced A1Z1Q3 140733 +ENSG00000172296 SPTLC3 bronchus respiratory epithelial cells High Enhanced Q9NUV7 55304 +ENSG00000172296 SPTLC3 lung macrophages Medium Enhanced Q9NUV7 55304 +ENSG00000172322 CLEC12A lung macrophages Low Enhanced Q5QGZ9 160364 +ENSG00000172331 BPGM bronchus respiratory epithelial cells Medium Enhanced P07738 669 +ENSG00000172340 SUCLG2 bronchus respiratory epithelial cells High Enhanced Q96I99 8801 +ENSG00000172340 SUCLG2 lung macrophages High Enhanced Q96I99 8801 +ENSG00000172361 CFAP53 bronchus respiratory epithelial cells Low Enhanced Q96M91 220136 +ENSG00000172379 ARNT2 bronchus respiratory epithelial cells Low Enhanced Q9HBZ2 9915 +ENSG00000172380 GNG12 bronchus respiratory epithelial cells Low Enhanced Q9UBI6 55970 +ENSG00000172409 CLP1 bronchus respiratory epithelial cells High Supported Q92989 10978 +ENSG00000172409 CLP1 lung macrophages High Supported Q92989 10978 +ENSG00000172409 CLP1 lung pneumocytes High Supported Q92989 10978 +ENSG00000172426 RSPH9 bronchus respiratory epithelial cells High Enhanced Q9H1X1 221421 +ENSG00000172466 ZNF24 bronchus respiratory epithelial cells High Supported P17028 7572 +ENSG00000172466 ZNF24 lung macrophages Medium Supported P17028 7572 +ENSG00000172466 ZNF24 lung pneumocytes High Supported P17028 7572 +ENSG00000172469 MANEA bronchus respiratory epithelial cells Low Enhanced Q5SRI9 79694 +ENSG00000172469 MANEA lung macrophages Low Enhanced Q5SRI9 79694 +ENSG00000172543 CTSW lung macrophages Medium Enhanced P56202 1521 +ENSG00000172613 RAD9A bronchus respiratory epithelial cells Medium Enhanced Q99638 5883 +ENSG00000172613 RAD9A lung macrophages High Enhanced Q99638 5883 +ENSG00000172613 RAD9A lung pneumocytes High Enhanced Q99638 5883 +ENSG00000172661 WASHC2C bronchus respiratory epithelial cells Medium Supported Q9Y4E1 253725 +ENSG00000172661 WASHC2C lung macrophages Medium Supported Q9Y4E1 253725 +ENSG00000172661 WASHC2C lung pneumocytes Low Supported Q9Y4E1 253725 +ENSG00000172667 ZMAT3 bronchus respiratory epithelial cells Medium Enhanced Q9HA38 64393 +ENSG00000172667 ZMAT3 lung macrophages Medium Enhanced Q9HA38 64393 +ENSG00000172667 ZMAT3 lung pneumocytes Medium Enhanced Q9HA38 64393 +ENSG00000172725 CORO1B bronchus respiratory epithelial cells Medium Enhanced Q9BR76 57175 +ENSG00000172725 CORO1B lung macrophages Medium Enhanced Q9BR76 57175 +ENSG00000172725 CORO1B lung pneumocytes Low Enhanced Q9BR76 57175 +ENSG00000172780 RAB43 bronchus respiratory epithelial cells Low Enhanced Q86YS6 339122 +ENSG00000172780 RAB43 lung pneumocytes Medium Enhanced Q86YS6 339122 +ENSG00000172819 RARG bronchus respiratory epithelial cells Medium Supported P13631 5916 +ENSG00000172819 RARG lung macrophages Medium Supported P13631 5916 +ENSG00000172819 RARG lung pneumocytes Medium Supported P13631 5916 +ENSG00000172831 CES2 bronchus respiratory epithelial cells Medium Enhanced O00748 8824 +ENSG00000172831 CES2 lung pneumocytes Medium Enhanced O00748 8824 +ENSG00000172845 SP3 bronchus respiratory epithelial cells Medium Supported Q02447 6670 +ENSG00000172845 SP3 lung macrophages Low Supported Q02447 6670 +ENSG00000172845 SP3 lung pneumocytes Medium Supported Q02447 6670 +ENSG00000172915 NBEA bronchus respiratory epithelial cells Medium Enhanced Q8NFP9 26960 +ENSG00000172915 NBEA lung macrophages Medium Enhanced Q8NFP9 26960 +ENSG00000172939 OXSR1 bronchus respiratory epithelial cells Medium Enhanced O95747 9943 +ENSG00000172939 OXSR1 lung macrophages Medium Enhanced O95747 9943 +ENSG00000172939 OXSR1 lung pneumocytes High Enhanced O95747 9943 +ENSG00000173013 CCDC96 bronchus respiratory epithelial cells Low Enhanced Q2M329 257236 +ENSG00000173039 RELA bronchus respiratory epithelial cells Low Supported Q04206 5970 +ENSG00000173039 RELA lung macrophages High Supported Q04206 5970 +ENSG00000173039 RELA lung pneumocytes Medium Supported Q04206 5970 +ENSG00000173120 KDM2A bronchus respiratory epithelial cells High Supported Q9Y2K7 22992 +ENSG00000173120 KDM2A lung macrophages High Supported Q9Y2K7 22992 +ENSG00000173120 KDM2A lung pneumocytes High Supported Q9Y2K7 22992 +ENSG00000173141 MRPL57 bronchus respiratory epithelial cells Medium Enhanced Q9BQC6 78988 +ENSG00000173141 MRPL57 lung macrophages Medium Enhanced Q9BQC6 78988 +ENSG00000173193 PARP14 bronchus respiratory epithelial cells High Supported Q460N5 54625 +ENSG00000173193 PARP14 lung macrophages Medium Supported Q460N5 54625 +ENSG00000173193 PARP14 lung pneumocytes Medium Supported Q460N5 54625 +ENSG00000173230 GOLGB1 bronchus respiratory epithelial cells High Enhanced Q14789 2804 +ENSG00000173230 GOLGB1 lung macrophages High Enhanced Q14789 2804 +ENSG00000173230 GOLGB1 lung pneumocytes High Enhanced Q14789 2804 +ENSG00000173276 ZBTB21 bronchus respiratory epithelial cells High Enhanced Q9ULJ3 49854 +ENSG00000173276 ZBTB21 lung macrophages Low Enhanced Q9ULJ3 49854 +ENSG00000173276 ZBTB21 lung pneumocytes Low Enhanced Q9ULJ3 49854 +ENSG00000173372 C1QA lung macrophages Medium Supported P02745 712 +ENSG00000173402 DAG1 bronchus respiratory epithelial cells Low Enhanced Q14118 1605 +ENSG00000173402 DAG1 lung macrophages Low Enhanced Q14118 1605 +ENSG00000173402 DAG1 lung pneumocytes Low Enhanced Q14118 1605 +ENSG00000173436 MINOS1 bronchus respiratory epithelial cells High Enhanced Q5TGZ0 440574 +ENSG00000173436 MINOS1 lung macrophages Low Enhanced Q5TGZ0 440574 +ENSG00000173436 MINOS1 lung pneumocytes Low Enhanced Q5TGZ0 440574 +ENSG00000173467 AGR3 bronchus respiratory epithelial cells High Enhanced Q8TD06 155465 +ENSG00000173467 AGR3 lung pneumocytes High Enhanced Q8TD06 155465 +ENSG00000173473 SMARCC1 bronchus respiratory epithelial cells Medium Enhanced Q92922 6599 +ENSG00000173473 SMARCC1 lung macrophages Low Enhanced Q92922 6599 +ENSG00000173482 PTPRM bronchus respiratory epithelial cells Low Supported P28827 5797 +ENSG00000173482 PTPRM lung macrophages Medium Supported P28827 5797 +ENSG00000173482 PTPRM lung pneumocytes Medium Supported P28827 5797 +ENSG00000173486 FKBP2 bronchus respiratory epithelial cells Low Enhanced P26885 2286 +ENSG00000173486 FKBP2 lung pneumocytes Low Enhanced P26885 2286 +ENSG00000173542 MOB1B bronchus respiratory epithelial cells Medium Supported Q7L9L4 92597 +ENSG00000173542 MOB1B lung macrophages Medium Supported Q7L9L4 92597 +ENSG00000173542 MOB1B lung pneumocytes Low Supported Q7L9L4 92597 +ENSG00000173575 CHD2 bronchus respiratory epithelial cells Low Enhanced O14647 1106 +ENSG00000173575 CHD2 lung macrophages Medium Enhanced O14647 1106 +ENSG00000173575 CHD2 lung pneumocytes Medium Enhanced O14647 1106 +ENSG00000173660 UQCRH bronchus respiratory epithelial cells Medium Supported P07919 7388 +ENSG00000173660 UQCRH lung pneumocytes Medium Supported P07919 7388 +ENSG00000173692 PSMD1 bronchus respiratory epithelial cells Medium Enhanced Q99460 5707 +ENSG00000173692 PSMD1 lung macrophages Low Enhanced Q99460 5707 +ENSG00000173692 PSMD1 lung pneumocytes Low Enhanced Q99460 5707 +ENSG00000173726 TOMM20 bronchus respiratory epithelial cells High Supported Q15388 9804 +ENSG00000173726 TOMM20 lung macrophages High Supported Q15388 9804 +ENSG00000173726 TOMM20 lung pneumocytes Low Supported Q15388 9804 +ENSG00000173801 JUP bronchus respiratory epithelial cells High Supported P14923 3728 +ENSG00000173801 JUP lung macrophages Low Supported P14923 3728 +ENSG00000173801 JUP lung pneumocytes Low Supported P14923 3728 +ENSG00000173846 PLK3 bronchus respiratory epithelial cells Medium Enhanced Q9H4B4 1263 +ENSG00000173846 PLK3 lung macrophages Medium Enhanced Q9H4B4 1263 +ENSG00000173846 PLK3 lung pneumocytes Medium Enhanced Q9H4B4 1263 +ENSG00000173898 SPTBN2 bronchus respiratory epithelial cells Low Enhanced O15020 6712 +ENSG00000173898 SPTBN2 lung macrophages Low Enhanced O15020 6712 +ENSG00000173905 GOLIM4 bronchus respiratory epithelial cells Medium Enhanced O00461 27333 +ENSG00000173905 GOLIM4 lung macrophages Low Enhanced O00461 27333 +ENSG00000173905 GOLIM4 lung pneumocytes Medium Enhanced O00461 27333 +ENSG00000173960 UBXN2A bronchus respiratory epithelial cells High Supported P68543 165324 +ENSG00000173960 UBXN2A lung macrophages Medium Supported P68543 165324 +ENSG00000173960 UBXN2A lung pneumocytes Medium Supported P68543 165324 +ENSG00000174007 CEP19 bronchus respiratory epithelial cells Low Enhanced Q96LK0 84984 +ENSG00000174007 CEP19 lung macrophages Medium Enhanced Q96LK0 84984 +ENSG00000174137 FAM53A bronchus respiratory epithelial cells Low Enhanced Q6NSI3 152877 +ENSG00000174137 FAM53A lung macrophages Low Enhanced Q6NSI3 152877 +ENSG00000174137 FAM53A lung pneumocytes Low Enhanced Q6NSI3 152877 +ENSG00000174231 PRPF8 bronchus respiratory epithelial cells High Supported I3L1T8 NA +ENSG00000174231 PRPF8 lung macrophages Medium Supported I3L1T8 NA +ENSG00000174231 PRPF8 lung pneumocytes Low Supported I3L1T8 NA +ENSG00000174282 ZBTB4 bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000174282 ZBTB4 lung macrophages Low Supported NA NA +ENSG00000174405 LIG4 bronchus respiratory epithelial cells Medium Supported P49917 3981 +ENSG00000174405 LIG4 lung macrophages Medium Supported P49917 3981 +ENSG00000174405 LIG4 lung pneumocytes Medium Supported P49917 3981 +ENSG00000174437 ATP2A2 bronchus respiratory epithelial cells Medium Enhanced P16615 488 +ENSG00000174437 ATP2A2 lung macrophages Low Enhanced P16615 488 +ENSG00000174640 SLCO2A1 bronchus respiratory epithelial cells Low Enhanced Q92959 6578 +ENSG00000174640 SLCO2A1 lung macrophages Low Enhanced Q92959 6578 +ENSG00000174844 DNAH12 bronchus respiratory epithelial cells Low Enhanced Q6ZR08 201625 +ENSG00000174891 RSRC1 bronchus respiratory epithelial cells Medium Enhanced Q96IZ7 51319 +ENSG00000174891 RSRC1 lung pneumocytes Low Enhanced Q96IZ7 51319 +ENSG00000174938 SEZ6L2 bronchus respiratory epithelial cells Medium Enhanced Q6UXD5 26470 +ENSG00000174943 KCTD13 bronchus respiratory epithelial cells Medium Enhanced Q8WZ19 253980 +ENSG00000174943 KCTD13 lung macrophages Medium Enhanced Q8WZ19 253980 +ENSG00000174943 KCTD13 lung pneumocytes Medium Enhanced Q8WZ19 253980 +ENSG00000174989 FBXW8 lung macrophages Medium Enhanced Q8N3Y1 26259 +ENSG00000174989 FBXW8 lung pneumocytes Low Enhanced Q8N3Y1 26259 +ENSG00000174996 KLC2 bronchus respiratory epithelial cells High Enhanced Q9H0B6 64837 +ENSG00000174996 KLC2 lung macrophages Medium Enhanced Q9H0B6 64837 +ENSG00000174996 KLC2 lung pneumocytes Low Enhanced Q9H0B6 64837 +ENSG00000175110 MRPS22 bronchus respiratory epithelial cells High Enhanced P82650 56945 +ENSG00000175110 MRPS22 lung macrophages High Enhanced P82650 56945 +ENSG00000175110 MRPS22 lung pneumocytes Medium Enhanced P82650 56945 +ENSG00000175198 PCCA bronchus respiratory epithelial cells Medium Enhanced P05165 5095 +ENSG00000175198 PCCA lung macrophages Medium Enhanced P05165 5095 +ENSG00000175198 PCCA lung pneumocytes Low Enhanced P05165 5095 +ENSG00000175203 DCTN2 bronchus respiratory epithelial cells High Enhanced Q13561 10540 +ENSG00000175216 CKAP5 bronchus respiratory epithelial cells High Enhanced Q14008 9793 +ENSG00000175216 CKAP5 lung macrophages High Enhanced Q14008 9793 +ENSG00000175216 CKAP5 lung pneumocytes Medium Enhanced Q14008 9793 +ENSG00000175305 CCNE2 bronchus respiratory epithelial cells Low Enhanced O96020 9134 +ENSG00000175305 CCNE2 lung macrophages Low Enhanced O96020 9134 +ENSG00000175305 CCNE2 lung pneumocytes Low Enhanced O96020 9134 +ENSG00000175334 BANF1 bronchus respiratory epithelial cells Medium Enhanced O75531 8815 +ENSG00000175334 BANF1 lung macrophages Low Enhanced O75531 8815 +ENSG00000175334 BANF1 lung pneumocytes Low Enhanced O75531 8815 +ENSG00000175344 CHRNA7 bronchus respiratory epithelial cells Medium Enhanced P36544 1139; 89832 +ENSG00000175354 PTPN2 bronchus respiratory epithelial cells Medium Enhanced P17706 5771 +ENSG00000175354 PTPN2 lung macrophages Medium Enhanced P17706 5771 +ENSG00000175354 PTPN2 lung pneumocytes Medium Enhanced P17706 5771 +ENSG00000175467 SART1 bronchus respiratory epithelial cells High Supported O43290 9092 +ENSG00000175600 SUGCT bronchus respiratory epithelial cells Medium Enhanced Q9HAC7 79783 +ENSG00000175600 SUGCT lung macrophages Medium Enhanced Q9HAC7 79783 +ENSG00000175600 SUGCT lung pneumocytes Medium Enhanced Q9HAC7 79783 +ENSG00000175662 TOM1L2 bronchus respiratory epithelial cells Medium Enhanced Q6ZVM7 146691 +ENSG00000175711 B3GNTL1 bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000175711 B3GNTL1 lung macrophages Medium Supported NA NA +ENSG00000175711 B3GNTL1 lung pneumocytes Low Supported NA NA +ENSG00000175792 RUVBL1 bronchus respiratory epithelial cells High Enhanced Q9Y265 8607 +ENSG00000175792 RUVBL1 lung macrophages Low Enhanced Q9Y265 8607 +ENSG00000175793 SFN lung macrophages Low Enhanced P31947 2810 +ENSG00000175866 BAIAP2 bronchus respiratory epithelial cells Medium Enhanced Q9UQB8 10458 +ENSG00000175866 BAIAP2 lung macrophages Medium Enhanced Q9UQB8 10458 +ENSG00000175866 BAIAP2 lung pneumocytes Medium Enhanced Q9UQB8 10458 +ENSG00000175899 A2M bronchus respiratory epithelial cells Medium Supported P01023 2 +ENSG00000175899 A2M lung macrophages Low Supported P01023 2 +ENSG00000175899 A2M lung pneumocytes Low Supported P01023 2 +ENSG00000175928 LRRN1 bronchus respiratory epithelial cells Medium Enhanced Q6UXK5 57633 +ENSG00000175928 LRRN1 lung macrophages Low Enhanced Q6UXK5 57633 +ENSG00000175928 LRRN1 lung pneumocytes Medium Enhanced Q6UXK5 57633 +ENSG00000176102 CSTF3 bronchus respiratory epithelial cells High Enhanced Q12996 1479 +ENSG00000176102 CSTF3 lung macrophages Medium Enhanced Q12996 1479 +ENSG00000176102 CSTF3 lung pneumocytes Medium Enhanced Q12996 1479 +ENSG00000176171 BNIP3 bronchus respiratory epithelial cells Medium Supported Q12983 664 +ENSG00000176171 BNIP3 lung macrophages Medium Supported Q12983 664 +ENSG00000176171 BNIP3 lung pneumocytes Low Supported Q12983 664 +ENSG00000176248 ANAPC2 bronchus respiratory epithelial cells Medium Enhanced Q9UJX6 29882 +ENSG00000176248 ANAPC2 lung macrophages Medium Enhanced Q9UJX6 29882 +ENSG00000176340 COX8A bronchus respiratory epithelial cells Medium Supported P10176 1351 +ENSG00000176371 ZSCAN2 bronchus respiratory epithelial cells High Supported Q7Z7L9 54993 +ENSG00000176371 ZSCAN2 lung macrophages High Supported Q7Z7L9 54993 +ENSG00000176371 ZSCAN2 lung pneumocytes High Supported Q7Z7L9 54993 +ENSG00000176387 HSD11B2 lung macrophages Low Enhanced P80365 3291 +ENSG00000176390 CRLF3 bronchus respiratory epithelial cells Low Enhanced Q8IUI8 51379 +ENSG00000176390 CRLF3 lung macrophages High Enhanced Q8IUI8 51379 +ENSG00000176406 RIMS2 bronchus respiratory epithelial cells High Enhanced Q9UQ26 9699 +ENSG00000176407 KCMF1 bronchus respiratory epithelial cells Medium Enhanced Q9P0J7 56888 +ENSG00000176407 KCMF1 lung macrophages Medium Enhanced Q9P0J7 56888 +ENSG00000176532 PRR15 bronchus respiratory epithelial cells Low Enhanced Q8IV56 222171 +ENSG00000176532 PRR15 lung pneumocytes Medium Enhanced Q8IV56 222171 +ENSG00000176619 LMNB2 bronchus respiratory epithelial cells Medium Enhanced Q03252 84823 +ENSG00000176619 LMNB2 lung pneumocytes Medium Enhanced Q03252 84823 +ENSG00000176788 BASP1 bronchus respiratory epithelial cells High Enhanced P80723 10409 +ENSG00000176890 TYMS bronchus respiratory epithelial cells Low Enhanced P04818 7298 +ENSG00000176890 TYMS lung macrophages Medium Enhanced P04818 7298 +ENSG00000176978 DPP7 bronchus respiratory epithelial cells Medium Supported Q9UHL4 29952 +ENSG00000176978 DPP7 lung macrophages High Supported Q9UHL4 29952 +ENSG00000176986 SEC24C bronchus respiratory epithelial cells Medium Supported P53992 9632 +ENSG00000176986 SEC24C lung macrophages Medium Supported P53992 9632 +ENSG00000176986 SEC24C lung pneumocytes Medium Supported P53992 9632 +ENSG00000177105 RHOG lung macrophages Low Enhanced P84095 391 +ENSG00000177105 RHOG lung pneumocytes Low Enhanced P84095 391 +ENSG00000177303 CASKIN2 bronchus respiratory epithelial cells Medium Enhanced Q8WXE0 57513 +ENSG00000177303 CASKIN2 lung pneumocytes Medium Enhanced Q8WXE0 57513 +ENSG00000177363 LRRN4CL bronchus respiratory epithelial cells Low Enhanced Q8ND94 221091 +ENSG00000177363 LRRN4CL lung macrophages Medium Enhanced Q8ND94 221091 +ENSG00000177409 SAMD9L bronchus respiratory epithelial cells Medium Enhanced Q8IVG5 219285 +ENSG00000177409 SAMD9L lung macrophages Medium Enhanced Q8IVG5 219285 +ENSG00000177409 SAMD9L lung pneumocytes Medium Enhanced Q8IVG5 219285 +ENSG00000177459 ERICH5 bronchus respiratory epithelial cells High Enhanced Q6P6B1 203111 +ENSG00000177465 ACOT4 bronchus respiratory epithelial cells Medium Enhanced Q8N9L9 122970 +ENSG00000177465 ACOT4 lung macrophages High Enhanced Q8N9L9 122970 +ENSG00000177469 PTRF bronchus respiratory epithelial cells Low Supported Q6NZI2 284119 +ENSG00000177469 PTRF lung macrophages Medium Supported Q6NZI2 284119 +ENSG00000177469 PTRF lung pneumocytes Medium Supported Q6NZI2 284119 +ENSG00000177565 TBL1XR1 bronchus respiratory epithelial cells High Supported Q9BZK7 79718 +ENSG00000177565 TBL1XR1 lung pneumocytes High Supported Q9BZK7 79718 +ENSG00000177575 CD163 lung macrophages High Enhanced Q86VB7 9332 +ENSG00000177595 PIDD1 bronchus respiratory epithelial cells High Supported Q9HB75 55367 +ENSG00000177595 PIDD1 lung macrophages Medium Supported Q9HB75 55367 +ENSG00000177595 PIDD1 lung pneumocytes High Supported Q9HB75 55367 +ENSG00000177606 JUN bronchus respiratory epithelial cells Medium Enhanced P05412 3725 +ENSG00000177606 JUN lung macrophages High Enhanced P05412 3725 +ENSG00000177606 JUN lung pneumocytes Medium Enhanced P05412 3725 +ENSG00000177628 GBA bronchus respiratory epithelial cells High Supported P04062 2629 +ENSG00000177628 GBA lung macrophages High Supported P04062 2629 +ENSG00000177628 GBA lung pneumocytes Low Supported P04062 2629 +ENSG00000177646 ACAD9 bronchus respiratory epithelial cells Medium Supported Q9H845 28976 +ENSG00000177646 ACAD9 lung macrophages Medium Supported Q9H845 28976 +ENSG00000177646 ACAD9 lung pneumocytes Medium Supported Q9H845 28976 +ENSG00000177663 IL17RA bronchus respiratory epithelial cells Medium Enhanced Q96F46 23765 +ENSG00000177663 IL17RA lung macrophages Medium Enhanced Q96F46 23765 +ENSG00000177697 CD151 bronchus respiratory epithelial cells Medium Supported P48509 977 +ENSG00000177697 CD151 lung macrophages Low Supported P48509 977 +ENSG00000177697 CD151 lung pneumocytes Medium Supported P48509 977 +ENSG00000177733 HNRNPA0 bronchus respiratory epithelial cells Medium Enhanced Q13151 10949 +ENSG00000177733 HNRNPA0 lung pneumocytes Low Enhanced Q13151 10949 +ENSG00000177889 UBE2N bronchus respiratory epithelial cells Medium Enhanced P61088 7334 +ENSG00000177889 UBE2N lung macrophages Medium Enhanced P61088 7334 +ENSG00000177917 ARL6IP6 lung macrophages Low Enhanced Q8N6S5 151188 +ENSG00000177917 ARL6IP6 lung pneumocytes Medium Enhanced Q8N6S5 151188 +ENSG00000177989 ODF3B bronchus respiratory epithelial cells High Enhanced A8MYP8 440836 +ENSG00000178057 NDUFAF3 bronchus respiratory epithelial cells High Enhanced Q9BU61 25915 +ENSG00000178057 NDUFAF3 lung macrophages Medium Enhanced Q9BU61 25915 +ENSG00000178057 NDUFAF3 lung pneumocytes Medium Enhanced Q9BU61 25915 +ENSG00000178127 NDUFV2 bronchus respiratory epithelial cells High Supported P19404 4729 +ENSG00000178127 NDUFV2 lung macrophages Medium Supported P19404 4729 +ENSG00000178209 PLEC bronchus respiratory epithelial cells Medium Enhanced Q15149 5339 +ENSG00000178209 PLEC lung macrophages High Enhanced Q15149 5339 +ENSG00000178209 PLEC lung pneumocytes Low Enhanced Q15149 5339 +ENSG00000178467 P4HTM bronchus respiratory epithelial cells Medium Supported Q9NXG6 54681 +ENSG00000178467 P4HTM lung macrophages Medium Supported Q9NXG6 54681 +ENSG00000178467 P4HTM lung pneumocytes Medium Supported Q9NXG6 54681 +ENSG00000178568 ERBB4 lung macrophages Medium Enhanced Q15303 2066 +ENSG00000178568 ERBB4 lung pneumocytes Medium Enhanced Q15303 2066 +ENSG00000178607 ERN1 bronchus respiratory epithelial cells High Supported O75460 2081 +ENSG00000178607 ERN1 lung macrophages Medium Supported O75460 2081 +ENSG00000178607 ERN1 lung pneumocytes Medium Supported O75460 2081 +ENSG00000178662 CSRNP3 bronchus respiratory epithelial cells High Supported Q8WYN3 80034 +ENSG00000178662 CSRNP3 lung macrophages Medium Supported Q8WYN3 80034 +ENSG00000178662 CSRNP3 lung pneumocytes High Supported Q8WYN3 80034 +ENSG00000178741 COX5A bronchus respiratory epithelial cells High Supported P20674 9377 +ENSG00000178741 COX5A lung macrophages High Supported P20674 9377 +ENSG00000178741 COX5A lung pneumocytes Medium Supported P20674 9377 +ENSG00000178764 ZHX2 bronchus respiratory epithelial cells Low Enhanced Q9Y6X8 22882 +ENSG00000178764 ZHX2 lung macrophages Low Enhanced Q9Y6X8 22882 +ENSG00000178764 ZHX2 lung pneumocytes Medium Enhanced Q9Y6X8 22882 +ENSG00000178796 RIIAD1 bronchus respiratory epithelial cells Medium Enhanced A6NNX1 284485 +ENSG00000178828 RNF186 bronchus respiratory epithelial cells Low Enhanced Q9NXI6 54546 +ENSG00000178921 PFAS lung macrophages Low Enhanced O15067 5198 +ENSG00000178951 ZBTB7A bronchus respiratory epithelial cells High Enhanced O95365 51341 +ENSG00000178951 ZBTB7A lung macrophages Medium Enhanced O95365 51341 +ENSG00000178952 TUFM bronchus respiratory epithelial cells High Enhanced P49411 7284 +ENSG00000178952 TUFM lung macrophages High Enhanced P49411 7284 +ENSG00000178952 TUFM lung pneumocytes High Enhanced P49411 7284 +ENSG00000178999 AURKB bronchus respiratory epithelial cells Low Enhanced Q96GD4 9212 +ENSG00000178999 AURKB lung macrophages Low Enhanced Q96GD4 9212 +ENSG00000179091 CYC1 bronchus respiratory epithelial cells High Supported P08574 1537 +ENSG00000179091 CYC1 lung macrophages High Supported P08574 1537 +ENSG00000179091 CYC1 lung pneumocytes Medium Supported P08574 1537 +ENSG00000179144 GIMAP7 lung macrophages Low Enhanced Q8NHV1 168537 +ENSG00000179144 GIMAP7 lung pneumocytes High Enhanced Q8NHV1 168537 +ENSG00000179163 FUCA1 bronchus respiratory epithelial cells Low Enhanced P04066 2517 +ENSG00000179163 FUCA1 lung macrophages Low Enhanced P04066 2517 +ENSG00000179218 CALR bronchus respiratory epithelial cells Low Enhanced P27797 811 +ENSG00000179218 CALR lung macrophages Medium Enhanced P27797 811 +ENSG00000179218 CALR lung pneumocytes Medium Enhanced P27797 811 +ENSG00000179262 RAD23A bronchus respiratory epithelial cells High Supported P54725 5886 +ENSG00000179262 RAD23A lung macrophages Medium Supported P54725 5886 +ENSG00000179262 RAD23A lung pneumocytes Medium Supported P54725 5886 +ENSG00000179271 GADD45GIP1 bronchus respiratory epithelial cells High Supported Q8TAE8 90480 +ENSG00000179361 ARID3B bronchus respiratory epithelial cells Medium Enhanced Q8IVW6 10620 +ENSG00000179361 ARID3B lung pneumocytes Low Enhanced Q8IVW6 10620 +ENSG00000179399 GPC5 bronchus respiratory epithelial cells Low Enhanced P78333 2262 +ENSG00000179399 GPC5 lung macrophages Medium Enhanced P78333 2262 +ENSG00000179399 GPC5 lung pneumocytes High Enhanced P78333 2262 +ENSG00000179562 GCC1 bronchus respiratory epithelial cells High Enhanced Q96CN9 79571 +ENSG00000179562 GCC1 lung macrophages Medium Enhanced Q96CN9 79571 +ENSG00000179562 GCC1 lung pneumocytes Medium Enhanced Q96CN9 79571 +ENSG00000179583 CIITA bronchus respiratory epithelial cells Medium Enhanced P33076 4261 +ENSG00000179583 CIITA lung macrophages High Enhanced P33076 4261 +ENSG00000179583 CIITA lung pneumocytes High Enhanced P33076 4261 +ENSG00000179588 ZFPM1 bronchus respiratory epithelial cells Medium Enhanced Q8IX07 161882 +ENSG00000179588 ZFPM1 lung macrophages High Enhanced Q8IX07 161882 +ENSG00000179593 ALOX15B bronchus respiratory epithelial cells Low Enhanced O15296 247 +ENSG00000179593 ALOX15B lung pneumocytes Low Enhanced O15296 247 +ENSG00000179636 TPPP2 bronchus respiratory epithelial cells Medium Enhanced P59282 122664 +ENSG00000179833 SERTAD2 bronchus respiratory epithelial cells High Enhanced Q14140 9792 +ENSG00000179833 SERTAD2 lung macrophages Medium Enhanced Q14140 9792 +ENSG00000179833 SERTAD2 lung pneumocytes Medium Enhanced Q14140 9792 +ENSG00000179902 C1orf194 bronchus respiratory epithelial cells Medium Enhanced Q5T5A4 127003 +ENSG00000179921 GPBAR1 bronchus respiratory epithelial cells Medium Enhanced Q8TDU6 151306 +ENSG00000179921 GPBAR1 lung macrophages Low Enhanced Q8TDU6 151306 +ENSG00000179921 GPBAR1 lung pneumocytes Medium Enhanced Q8TDU6 151306 +ENSG00000179950 PUF60 bronchus respiratory epithelial cells Medium Enhanced H0YEM1 NA +ENSG00000179950 PUF60 lung macrophages Medium Enhanced H0YEM1 NA +ENSG00000179950 PUF60 lung pneumocytes Medium Enhanced H0YEM1 NA +ENSG00000180185 FAHD1 bronchus respiratory epithelial cells Medium Enhanced Q6P587 81889 +ENSG00000180185 FAHD1 lung macrophages Medium Enhanced Q6P587 81889 +ENSG00000180185 FAHD1 lung pneumocytes Medium Enhanced Q6P587 81889 +ENSG00000180198 RCC1 bronchus respiratory epithelial cells High Enhanced P18754 1104 +ENSG00000180198 RCC1 lung macrophages Low Enhanced P18754 1104 +ENSG00000180198 RCC1 lung pneumocytes Medium Enhanced P18754 1104 +ENSG00000180353 HCLS1 lung macrophages Medium Supported P14317 3059 +ENSG00000180353 HCLS1 lung pneumocytes Low Supported P14317 3059 +ENSG00000180398 MCFD2 bronchus respiratory epithelial cells Medium Supported Q8NI22 90411 +ENSG00000180398 MCFD2 lung macrophages High Supported Q8NI22 90411 +ENSG00000180398 MCFD2 lung pneumocytes High Supported Q8NI22 90411 +ENSG00000180573 HIST1H2AC bronchus respiratory epithelial cells Medium Supported Q93077 8334 +ENSG00000180573 HIST1H2AC lung macrophages High Supported Q93077 8334 +ENSG00000180573 HIST1H2AC lung pneumocytes High Supported Q93077 8334 +ENSG00000180596 HIST1H2BC bronchus respiratory epithelial cells High Supported NA NA +ENSG00000180596 HIST1H2BC lung macrophages High Supported NA NA +ENSG00000180596 HIST1H2BC lung pneumocytes High Supported NA NA +ENSG00000180739 S1PR5 lung macrophages Low Enhanced Q9H228 53637 +ENSG00000180773 SLC36A4 bronchus respiratory epithelial cells High Enhanced Q6YBV0 120103 +ENSG00000180773 SLC36A4 lung macrophages High Enhanced Q6YBV0 120103 +ENSG00000180773 SLC36A4 lung pneumocytes High Enhanced Q6YBV0 120103 +ENSG00000180817 PPA1 bronchus respiratory epithelial cells High Supported Q15181 5464 +ENSG00000180817 PPA1 lung macrophages Medium Supported Q15181 5464 +ENSG00000180817 PPA1 lung pneumocytes High Supported Q15181 5464 +ENSG00000180855 ZNF443 bronchus respiratory epithelial cells Medium Supported Q9Y2A4 10224 +ENSG00000180855 ZNF443 lung macrophages Medium Supported Q9Y2A4 10224 +ENSG00000180855 ZNF443 lung pneumocytes Medium Supported Q9Y2A4 10224 +ENSG00000180879 SSR4 bronchus respiratory epithelial cells Medium Enhanced P51571 6748 +ENSG00000180879 SSR4 lung macrophages Medium Enhanced P51571 6748 +ENSG00000180879 SSR4 lung pneumocytes Low Enhanced P51571 6748 +ENSG00000180884 ZNF792 bronchus respiratory epithelial cells High Supported Q3KQV3 126375 +ENSG00000180884 ZNF792 lung macrophages Medium Supported Q3KQV3 126375 +ENSG00000180884 ZNF792 lung pneumocytes High Supported Q3KQV3 126375 +ENSG00000180900 SCRIB bronchus respiratory epithelial cells Medium Enhanced Q14160 23513 +ENSG00000180900 SCRIB lung macrophages Medium Enhanced Q14160 23513 +ENSG00000180921 FAM83H bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000180938 ZNF572 bronchus respiratory epithelial cells Medium Enhanced Q7Z3I7 137209 +ENSG00000180938 ZNF572 lung macrophages Low Enhanced Q7Z3I7 137209 +ENSG00000180938 ZNF572 lung pneumocytes Medium Enhanced Q7Z3I7 137209 +ENSG00000181019 NQO1 bronchus respiratory epithelial cells Medium Enhanced P15559 1728 +ENSG00000181019 NQO1 lung pneumocytes Low Enhanced P15559 1728 +ENSG00000181143 MUC16 bronchus respiratory epithelial cells High Enhanced Q8WXI7 94025 +ENSG00000181163 NPM1 bronchus respiratory epithelial cells High Supported P06748 4869 +ENSG00000181163 NPM1 lung macrophages High Supported P06748 4869 +ENSG00000181163 NPM1 lung pneumocytes High Supported P06748 4869 +ENSG00000181191 PJA1 bronchus respiratory epithelial cells High Enhanced Q8NG27 64219 +ENSG00000181191 PJA1 lung macrophages High Enhanced Q8NG27 64219 +ENSG00000181191 PJA1 lung pneumocytes Low Enhanced Q8NG27 64219 +ENSG00000181218 HIST3H2A bronchus respiratory epithelial cells Medium Supported Q7L7L0 92815 +ENSG00000181218 HIST3H2A lung macrophages High Supported Q7L7L0 92815 +ENSG00000181218 HIST3H2A lung pneumocytes High Supported Q7L7L0 92815 +ENSG00000181222 POLR2A bronchus respiratory epithelial cells Medium Enhanced P24928 5430 +ENSG00000181222 POLR2A lung macrophages Medium Enhanced P24928 5430 +ENSG00000181222 POLR2A lung pneumocytes Medium Enhanced P24928 5430 +ENSG00000181322 NME9 bronchus respiratory epithelial cells High Enhanced Q86XW9 347736 +ENSG00000181409 AATK lung macrophages Medium Enhanced Q6ZMQ8 9625 +ENSG00000181523 SGSH lung macrophages High Enhanced P51688 6448 +ENSG00000181610 MRPS23 bronchus respiratory epithelial cells Medium Supported Q9Y3D9 51649 +ENSG00000181610 MRPS23 lung macrophages Medium Supported Q9Y3D9 51649 +ENSG00000181610 MRPS23 lung pneumocytes Medium Supported Q9Y3D9 51649 +ENSG00000181631 P2RY13 lung macrophages Low Enhanced Q9BPV8 53829 +ENSG00000181789 COPG1 bronchus respiratory epithelial cells High Supported Q9Y678 22820 +ENSG00000181789 COPG1 lung macrophages High Supported Q9Y678 22820 +ENSG00000181789 COPG1 lung pneumocytes Medium Supported Q9Y678 22820 +ENSG00000181827 RFX7 bronchus respiratory epithelial cells Medium Supported Q2KHR2 64864 +ENSG00000181827 RFX7 lung macrophages Low Supported Q2KHR2 64864 +ENSG00000181827 RFX7 lung pneumocytes Medium Supported Q2KHR2 64864 +ENSG00000181830 SLC35C1 bronchus respiratory epithelial cells Medium Enhanced Q96A29 55343 +ENSG00000181830 SLC35C1 lung macrophages Low Enhanced Q96A29 55343 +ENSG00000181885 CLDN7 bronchus respiratory epithelial cells High Enhanced O95471 1366 +ENSG00000181885 CLDN7 lung pneumocytes Low Enhanced O95471 1366 +ENSG00000181991 MRPS11 bronchus respiratory epithelial cells High Enhanced P82912 64963 +ENSG00000181991 MRPS11 lung macrophages High Enhanced P82912 64963 +ENSG00000182010 RTKN2 lung macrophages Medium Enhanced Q8IZC4 219790 +ENSG00000182054 IDH2 bronchus respiratory epithelial cells High Enhanced P48735 3418 +ENSG00000182054 IDH2 lung macrophages Medium Enhanced P48735 3418 +ENSG00000182117 NOP10 bronchus respiratory epithelial cells Medium Supported Q9NPE3 55505 +ENSG00000182117 NOP10 lung pneumocytes Low Supported Q9NPE3 55505 +ENSG00000182154 MRPL41 bronchus respiratory epithelial cells Medium Supported Q8IXM3 64975 +ENSG00000182154 MRPL41 lung macrophages Medium Supported Q8IXM3 64975 +ENSG00000182154 MRPL41 lung pneumocytes Low Supported Q8IXM3 64975 +ENSG00000182180 MRPS16 bronchus respiratory epithelial cells High Supported Q9Y3D3 51021 +ENSG00000182180 MRPS16 lung macrophages Medium Supported Q9Y3D3 51021 +ENSG00000182180 MRPS16 lung pneumocytes Medium Supported Q9Y3D3 51021 +ENSG00000182185 RAD51B bronchus respiratory epithelial cells High Enhanced O15315 5890 +ENSG00000182185 RAD51B lung macrophages High Enhanced O15315 5890 +ENSG00000182185 RAD51B lung pneumocytes High Enhanced O15315 5890 +ENSG00000182199 SHMT2 bronchus respiratory epithelial cells Medium Enhanced P34897 6472 +ENSG00000182199 SHMT2 lung macrophages Medium Enhanced P34897 6472 +ENSG00000182199 SHMT2 lung pneumocytes Low Enhanced P34897 6472 +ENSG00000182287 AP1S2 bronchus respiratory epithelial cells Low Enhanced P56377 8905 +ENSG00000182446 NPLOC4 bronchus respiratory epithelial cells High Enhanced Q8TAT6 55666 +ENSG00000182446 NPLOC4 lung macrophages Low Enhanced Q8TAT6 55666 +ENSG00000182473 EXOC7 bronchus respiratory epithelial cells High Supported Q9UPT5 23265 +ENSG00000182473 EXOC7 lung macrophages Medium Supported Q9UPT5 23265 +ENSG00000182473 EXOC7 lung pneumocytes Medium Supported Q9UPT5 23265 +ENSG00000182481 KPNA2 bronchus respiratory epithelial cells Low Enhanced P52292 3838 +ENSG00000182481 KPNA2 lung macrophages Medium Enhanced P52292 3838 +ENSG00000182492 BGN lung macrophages Low Enhanced P21810 633 +ENSG00000182504 CEP97 bronchus respiratory epithelial cells High Enhanced Q8IW35 79598 +ENSG00000182504 CEP97 lung macrophages Medium Enhanced Q8IW35 79598 +ENSG00000182568 SATB1 bronchus respiratory epithelial cells Low Supported Q01826 6304 +ENSG00000182580 EPHB3 lung macrophages Medium Enhanced P54753 2049 +ENSG00000182580 EPHB3 lung pneumocytes Low Enhanced P54753 2049 +ENSG00000182667 NTM lung macrophages Medium Enhanced Q9P121 50863 +ENSG00000182718 ANXA2 bronchus respiratory epithelial cells High Enhanced P07355 302 +ENSG00000182718 ANXA2 lung macrophages High Enhanced P07355 302 +ENSG00000182718 ANXA2 lung pneumocytes Medium Enhanced P07355 302 +ENSG00000182795 C1orf116 bronchus respiratory epithelial cells Medium Enhanced Q9BW04 79098 +ENSG00000182795 C1orf116 lung macrophages High Enhanced Q9BW04 79098 +ENSG00000182795 C1orf116 lung pneumocytes High Enhanced Q9BW04 79098 +ENSG00000182916 TCEAL7 bronchus respiratory epithelial cells Medium Enhanced Q9BRU2 56849 +ENSG00000182944 EWSR1 bronchus respiratory epithelial cells High Enhanced Q01844 2130 +ENSG00000182944 EWSR1 lung macrophages High Enhanced Q01844 2130 +ENSG00000182944 EWSR1 lung pneumocytes High Enhanced Q01844 2130 +ENSG00000182979 MTA1 bronchus respiratory epithelial cells Low Supported Q13330 9112 +ENSG00000182979 MTA1 lung macrophages Low Supported Q13330 9112 +ENSG00000182985 CADM1 bronchus respiratory epithelial cells Medium Enhanced Q9BY67 23705 +ENSG00000182985 CADM1 lung pneumocytes Medium Enhanced Q9BY67 23705 +ENSG00000183019 MCEMP1 lung macrophages High Enhanced Q8IX19 199675 +ENSG00000183020 AP2A2 bronchus respiratory epithelial cells High Enhanced O94973 161 +ENSG00000183020 AP2A2 lung macrophages High Enhanced O94973 161 +ENSG00000183044 ABAT bronchus respiratory epithelial cells Medium Enhanced P80404 18 +ENSG00000183048 SLC25A10 bronchus respiratory epithelial cells Medium Supported Q9UBX3 1468 +ENSG00000183048 SLC25A10 lung macrophages Medium Supported Q9UBX3 1468 +ENSG00000183048 SLC25A10 lung pneumocytes Medium Supported Q9UBX3 1468 +ENSG00000183049 CAMK1D bronchus respiratory epithelial cells Medium Enhanced Q8IU85 57118 +ENSG00000183049 CAMK1D lung macrophages Medium Enhanced Q8IU85 57118 +ENSG00000183049 CAMK1D lung pneumocytes Medium Enhanced Q8IU85 57118 +ENSG00000183160 TMEM119 bronchus respiratory epithelial cells Medium Enhanced Q4V9L6 338773 +ENSG00000183160 TMEM119 lung pneumocytes Low Enhanced Q4V9L6 338773 +ENSG00000183207 RUVBL2 bronchus respiratory epithelial cells High Enhanced Q9Y230 10856 +ENSG00000183258 DDX41 bronchus respiratory epithelial cells High Enhanced Q9UJV9 51428 +ENSG00000183258 DDX41 lung macrophages Medium Enhanced Q9UJV9 51428 +ENSG00000183258 DDX41 lung pneumocytes Medium Enhanced Q9UJV9 51428 +ENSG00000183336 BOLA2 bronchus respiratory epithelial cells Medium Supported A0A087WZT3 107984053; 552900; 654483 +ENSG00000183336 BOLA2 lung macrophages Low Supported A0A087WZT3 107984053; 552900; 654483 +ENSG00000183346 C10orf107 bronchus respiratory epithelial cells High Enhanced Q8IVU9 219621 +ENSG00000183426 NPIPA1 bronchus respiratory epithelial cells Medium Supported Q9UND3 642799; 9284 +ENSG00000183426 NPIPA1 lung macrophages High Supported Q9UND3 642799; 9284 +ENSG00000183426 NPIPA1 lung pneumocytes High Supported Q9UND3 642799; 9284 +ENSG00000183431 SF3A3 bronchus respiratory epithelial cells High Enhanced Q12874 10946 +ENSG00000183431 SF3A3 lung macrophages Medium Enhanced Q12874 10946 +ENSG00000183431 SF3A3 lung pneumocytes Low Enhanced Q12874 10946 +ENSG00000183475 ASB7 bronchus respiratory epithelial cells Medium Enhanced Q9H672 140460 +ENSG00000183475 ASB7 lung macrophages Medium Enhanced Q9H672 140460 +ENSG00000183484 GPR132 bronchus respiratory epithelial cells High Supported Q9UNW8 29933 +ENSG00000183484 GPR132 lung macrophages Medium Supported Q9UNW8 29933 +ENSG00000183484 GPR132 lung pneumocytes High Supported Q9UNW8 29933 +ENSG00000183495 EP400 bronchus respiratory epithelial cells High Supported Q96L91 57634 +ENSG00000183495 EP400 lung macrophages Medium Supported Q96L91 57634 +ENSG00000183495 EP400 lung pneumocytes High Supported Q96L91 57634 +ENSG00000183598 HIST2H3D bronchus respiratory epithelial cells High Supported NA NA +ENSG00000183598 HIST2H3D lung macrophages Medium Supported NA NA +ENSG00000183598 HIST2H3D lung pneumocytes High Supported NA NA +ENSG00000183684 ALYREF bronchus respiratory epithelial cells High Supported Q86V81 10189 +ENSG00000183684 ALYREF lung macrophages High Supported Q86V81 10189 +ENSG00000183684 ALYREF lung pneumocytes High Supported Q86V81 10189 +ENSG00000183723 CMTM4 bronchus respiratory epithelial cells Medium Enhanced Q8IZR5 146223 +ENSG00000183723 CMTM4 lung macrophages Medium Enhanced Q8IZR5 146223 +ENSG00000183723 CMTM4 lung pneumocytes Low Enhanced Q8IZR5 146223 +ENSG00000183742 MACC1 bronchus respiratory epithelial cells High Supported Q6ZN28 346389 +ENSG00000183742 MACC1 lung macrophages High Supported Q6ZN28 346389 +ENSG00000183742 MACC1 lung pneumocytes Low Supported Q6ZN28 346389 +ENSG00000183751 TBL3 bronchus respiratory epithelial cells Low Enhanced Q12788 10607 +ENSG00000183763 TRAIP bronchus respiratory epithelial cells Medium Enhanced Q9BWF2 10293 +ENSG00000183763 TRAIP lung macrophages Low Enhanced Q9BWF2 10293 +ENSG00000183763 TRAIP lung pneumocytes Low Enhanced Q9BWF2 10293 +ENSG00000183765 CHEK2 bronchus respiratory epithelial cells High Enhanced O96017 11200 +ENSG00000183765 CHEK2 lung macrophages Medium Enhanced O96017 11200 +ENSG00000183765 CHEK2 lung pneumocytes Medium Enhanced O96017 11200 +ENSG00000183779 ZNF703 bronchus respiratory epithelial cells Medium Supported Q9H7S9 80139 +ENSG00000183779 ZNF703 lung macrophages Medium Supported Q9H7S9 80139 +ENSG00000183779 ZNF703 lung pneumocytes Medium Supported Q9H7S9 80139 +ENSG00000183831 ANKRD45 bronchus respiratory epithelial cells High Enhanced Q5TZF3 339416 +ENSG00000183878 UTY bronchus respiratory epithelial cells Low Supported O14607 7404 +ENSG00000183878 UTY lung macrophages Low Supported O14607 7404 +ENSG00000183878 UTY lung pneumocytes Low Supported O14607 7404 +ENSG00000183914 DNAH2 bronchus respiratory epithelial cells Medium Enhanced Q9P225 146754 +ENSG00000183943 PRKX bronchus respiratory epithelial cells Medium Supported P51817 5613 +ENSG00000183943 PRKX lung macrophages Medium Supported P51817 5613 +ENSG00000183943 PRKX lung pneumocytes High Supported P51817 5613 +ENSG00000184047 DIABLO bronchus respiratory epithelial cells Medium Enhanced Q9NR28 56616 +ENSG00000184047 DIABLO lung macrophages Low Enhanced Q9NR28 56616 +ENSG00000184047 DIABLO lung pneumocytes Low Enhanced Q9NR28 56616 +ENSG00000184110 EIF3C bronchus respiratory epithelial cells High Supported Q99613 8663 +ENSG00000184110 EIF3C lung macrophages Medium Supported Q99613 8663 +ENSG00000184110 EIF3C lung pneumocytes Medium Supported Q99613 8663 +ENSG00000184178 SCFD2 bronchus respiratory epithelial cells Medium Enhanced Q8WU76 152579 +ENSG00000184178 SCFD2 lung macrophages Medium Enhanced Q8WU76 152579 +ENSG00000184178 SCFD2 lung pneumocytes Low Enhanced Q8WU76 152579 +ENSG00000184209 SNRNP35 bronchus respiratory epithelial cells High Supported Q16560 11066 +ENSG00000184209 SNRNP35 lung macrophages Low Supported Q16560 11066 +ENSG00000184209 SNRNP35 lung pneumocytes High Supported Q16560 11066 +ENSG00000184216 IRAK1 bronchus respiratory epithelial cells Medium Supported P51617 3654 +ENSG00000184216 IRAK1 lung macrophages Medium Supported P51617 3654 +ENSG00000184216 IRAK1 lung pneumocytes Low Supported P51617 3654 +ENSG00000184254 ALDH1A3 bronchus respiratory epithelial cells Medium Enhanced P47895 220 +ENSG00000184254 ALDH1A3 lung macrophages Low Enhanced P47895 220 +ENSG00000184254 ALDH1A3 lung pneumocytes Low Enhanced P47895 220 +ENSG00000184260 HIST2H2AC bronchus respiratory epithelial cells Medium Supported Q16777 8338 +ENSG00000184260 HIST2H2AC lung macrophages High Supported Q16777 8338 +ENSG00000184260 HIST2H2AC lung pneumocytes High Supported Q16777 8338 +ENSG00000184270 HIST2H2AB bronchus respiratory epithelial cells Medium Supported Q8IUE6 317772 +ENSG00000184270 HIST2H2AB lung macrophages High Supported Q8IUE6 317772 +ENSG00000184270 HIST2H2AB lung pneumocytes High Supported Q8IUE6 317772 +ENSG00000184271 POU6F1 bronchus respiratory epithelial cells High Enhanced Q14863 5463 +ENSG00000184271 POU6F1 lung macrophages Medium Enhanced Q14863 5463 +ENSG00000184271 POU6F1 lung pneumocytes Medium Enhanced Q14863 5463 +ENSG00000184292 TACSTD2 bronchus respiratory epithelial cells Medium Enhanced P09758 4070 +ENSG00000184363 PKP3 bronchus respiratory epithelial cells Low Enhanced Q9Y446 11187 +ENSG00000184363 PKP3 lung macrophages High Enhanced Q9Y446 11187 +ENSG00000184368 MAP7D2 bronchus respiratory epithelial cells Low Enhanced Q96T17 256714 +ENSG00000184470 TXNRD2 bronchus respiratory epithelial cells Medium Supported Q9NNW7 10587 +ENSG00000184470 TXNRD2 lung macrophages Medium Supported Q9NNW7 10587 +ENSG00000184470 TXNRD2 lung pneumocytes Low Supported Q9NNW7 10587 +ENSG00000184500 PROS1 bronchus respiratory epithelial cells Medium Enhanced P07225 5627 +ENSG00000184500 PROS1 lung macrophages Medium Enhanced P07225 5627 +ENSG00000184584 TMEM173 bronchus respiratory epithelial cells High Enhanced Q86WV6 340061 +ENSG00000184584 TMEM173 lung macrophages High Enhanced Q86WV6 340061 +ENSG00000184584 TMEM173 lung pneumocytes Medium Enhanced Q86WV6 340061 +ENSG00000184634 MED12 bronchus respiratory epithelial cells High Enhanced Q93074 9968 +ENSG00000184634 MED12 lung macrophages High Enhanced Q93074 9968 +ENSG00000184634 MED12 lung pneumocytes High Enhanced Q93074 9968 +ENSG00000184678 HIST2H2BE bronchus respiratory epithelial cells High Supported Q16778 8349 +ENSG00000184678 HIST2H2BE lung macrophages High Supported Q16778 8349 +ENSG00000184678 HIST2H2BE lung pneumocytes High Supported Q16778 8349 +ENSG00000184708 EIF4ENIF1 bronchus respiratory epithelial cells High Enhanced Q9NRA8 56478 +ENSG00000184708 EIF4ENIF1 lung macrophages High Enhanced Q9NRA8 56478 +ENSG00000184708 EIF4ENIF1 lung pneumocytes High Enhanced Q9NRA8 56478 +ENSG00000184730 APOBR lung macrophages High Enhanced Q0VD83 55911 +ENSG00000184752 NDUFA12 bronchus respiratory epithelial cells High Supported Q9UI09 55967 +ENSG00000184752 NDUFA12 lung macrophages Medium Supported Q9UI09 55967 +ENSG00000184752 NDUFA12 lung pneumocytes Low Supported Q9UI09 55967 +ENSG00000184831 APOO bronchus respiratory epithelial cells High Supported Q9BUR5 79135 +ENSG00000184831 APOO lung macrophages Medium Supported Q9BUR5 79135 +ENSG00000184831 APOO lung pneumocytes Low Supported Q9BUR5 79135 +ENSG00000184897 H1FX bronchus respiratory epithelial cells Medium Supported Q92522 8971 +ENSG00000184897 H1FX lung macrophages Medium Supported Q92522 8971 +ENSG00000184897 H1FX lung pneumocytes Medium Supported Q92522 8971 +ENSG00000184900 SUMO3 bronchus respiratory epithelial cells High Supported P55854 6612 +ENSG00000184900 SUMO3 lung macrophages High Supported P55854 6612 +ENSG00000184900 SUMO3 lung pneumocytes Medium Supported P55854 6612 +ENSG00000184922 FMNL1 lung macrophages Medium Enhanced O95466 752 +ENSG00000185000 DGAT1 lung macrophages Low Enhanced O75907 8694 +ENSG00000185010 F8 bronchus respiratory epithelial cells Medium Enhanced P00451 2157 +ENSG00000185010 F8 lung macrophages Medium Enhanced P00451 2157 +ENSG00000185010 F8 lung pneumocytes Low Enhanced P00451 2157 +ENSG00000185015 CA13 bronchus respiratory epithelial cells Medium Enhanced Q8N1Q1 377677 +ENSG00000185015 CA13 lung macrophages Medium Enhanced Q8N1Q1 377677 +ENSG00000185015 CA13 lung pneumocytes Low Enhanced Q8N1Q1 377677 +ENSG00000185049 NELFA bronchus respiratory epithelial cells Medium Enhanced Q9H3P2 7469 +ENSG00000185049 NELFA lung macrophages High Enhanced Q9H3P2 7469 +ENSG00000185049 NELFA lung pneumocytes High Enhanced Q9H3P2 7469 +ENSG00000185122 HSF1 bronchus respiratory epithelial cells High Supported Q00613 3297 +ENSG00000185122 HSF1 lung macrophages High Supported Q00613 3297 +ENSG00000185122 HSF1 lung pneumocytes High Supported Q00613 3297 +ENSG00000185130 HIST1H2BL bronchus respiratory epithelial cells High Supported Q99880 8340 +ENSG00000185130 HIST1H2BL lung macrophages High Supported Q99880 8340 +ENSG00000185130 HIST1H2BL lung pneumocytes High Supported Q99880 8340 +ENSG00000185215 TNFAIP2 bronchus respiratory epithelial cells Medium Enhanced Q03169 7127 +ENSG00000185215 TNFAIP2 lung macrophages Medium Enhanced Q03169 7127 +ENSG00000185303 SFTPA2 lung macrophages High Enhanced Q8IWL1 729238 +ENSG00000185303 SFTPA2 lung pneumocytes High Enhanced Q8IWL1 729238 +ENSG00000185345 PARK2 bronchus respiratory epithelial cells Medium Enhanced O60260 5071 +ENSG00000185345 PARK2 lung macrophages Low Enhanced O60260 5071 +ENSG00000185479 KRT6B bronchus respiratory epithelial cells Medium Supported P04259 3854 +ENSG00000185499 MUC1 bronchus respiratory epithelial cells High Enhanced P15941 4582 +ENSG00000185499 MUC1 lung macrophages Low Enhanced P15941 4582 +ENSG00000185499 MUC1 lung pneumocytes Medium Enhanced P15941 4582 +ENSG00000185532 PRKG1 bronchus respiratory epithelial cells Medium Enhanced Q13976 5592 +ENSG00000185532 PRKG1 lung macrophages Medium Enhanced Q13976 5592 +ENSG00000185532 PRKG1 lung pneumocytes Medium Enhanced Q13976 5592 +ENSG00000185567 AHNAK2 bronchus respiratory epithelial cells High Enhanced Q8IVF2 113146 +ENSG00000185591 SP1 bronchus respiratory epithelial cells Medium Supported P08047 6667 +ENSG00000185591 SP1 lung macrophages Medium Supported P08047 6667 +ENSG00000185591 SP1 lung pneumocytes Medium Supported P08047 6667 +ENSG00000185624 P4HB bronchus respiratory epithelial cells Medium Enhanced P07237 5034 +ENSG00000185624 P4HB lung macrophages Medium Enhanced P07237 5034 +ENSG00000185624 P4HB lung pneumocytes Medium Enhanced P07237 5034 +ENSG00000185630 PBX1 bronchus respiratory epithelial cells Medium Supported P40424 5087 +ENSG00000185630 PBX1 lung pneumocytes Low Supported P40424 5087 +ENSG00000185640 KRT79 bronchus respiratory epithelial cells Low Enhanced Q5XKE5 338785 +ENSG00000185670 ZBTB3 bronchus respiratory epithelial cells Medium Enhanced Q9H5J0 79842 +ENSG00000185670 ZBTB3 lung macrophages Medium Enhanced Q9H5J0 79842 +ENSG00000185813 PCYT2 bronchus respiratory epithelial cells High Enhanced Q99447 5833 +ENSG00000185813 PCYT2 lung macrophages Low Enhanced Q99447 5833 +ENSG00000185813 PCYT2 lung pneumocytes Medium Enhanced Q99447 5833 +ENSG00000185825 BCAP31 bronchus respiratory epithelial cells Medium Enhanced P51572 10134 +ENSG00000185825 BCAP31 lung macrophages Medium Enhanced P51572 10134 +ENSG00000185825 BCAP31 lung pneumocytes Medium Enhanced P51572 10134 +ENSG00000185862 EVI2B bronchus respiratory epithelial cells Medium Enhanced P34910 2124 +ENSG00000185862 EVI2B lung macrophages High Enhanced P34910 2124 +ENSG00000185862 EVI2B lung pneumocytes Low Enhanced P34910 2124 +ENSG00000185885 IFITM1 bronchus respiratory epithelial cells Low Enhanced P13164 8519 +ENSG00000185896 LAMP1 bronchus respiratory epithelial cells High Enhanced P11279 3916 +ENSG00000185896 LAMP1 lung macrophages High Enhanced P11279 3916 +ENSG00000185896 LAMP1 lung pneumocytes High Enhanced P11279 3916 +ENSG00000185909 KLHDC8B bronchus respiratory epithelial cells Medium Supported Q8IXV7 200942 +ENSG00000185909 KLHDC8B lung macrophages Medium Supported Q8IXV7 200942 +ENSG00000185963 BICD2 bronchus respiratory epithelial cells Medium Enhanced Q8TD16 23299 +ENSG00000185963 BICD2 lung macrophages Medium Enhanced Q8TD16 23299 +ENSG00000185988 PLK5 bronchus respiratory epithelial cells High Enhanced Q496M5 126520 +ENSG00000186010 NDUFA13 bronchus respiratory epithelial cells Medium Supported Q9P0J0 51079 +ENSG00000186010 NDUFA13 lung macrophages High Supported Q9P0J0 51079 +ENSG00000186010 NDUFA13 lung pneumocytes Low Supported Q9P0J0 51079 +ENSG00000186074 CD300LF lung macrophages Medium Supported Q8TDQ1 146722 +ENSG00000186081 KRT5 bronchus respiratory epithelial cells High Enhanced P13647 3852 +ENSG00000186185 KIF18B lung macrophages Low Enhanced Q86Y91 146909 +ENSG00000186260 MKL2 bronchus respiratory epithelial cells High Supported Q9ULH7 57496 +ENSG00000186260 MKL2 lung macrophages Medium Supported Q9ULH7 57496 +ENSG00000186260 MKL2 lung pneumocytes Medium Supported Q9ULH7 57496 +ENSG00000186265 BTLA lung macrophages Low Enhanced Q7Z6A9 151888 +ENSG00000186350 RXRA bronchus respiratory epithelial cells High Supported P19793 6256 +ENSG00000186350 RXRA lung macrophages High Supported P19793 6256 +ENSG00000186350 RXRA lung pneumocytes High Supported P19793 6256 +ENSG00000186364 NUDT17 bronchus respiratory epithelial cells High Enhanced P0C025 200035 +ENSG00000186364 NUDT17 lung macrophages Medium Enhanced P0C025 200035 +ENSG00000186364 NUDT17 lung pneumocytes Low Enhanced P0C025 200035 +ENSG00000186376 ZNF75D lung macrophages High Supported P51815 7626 +ENSG00000186376 ZNF75D lung pneumocytes High Supported P51815 7626 +ENSG00000186432 KPNA4 bronchus respiratory epithelial cells High Enhanced O00629 3840 +ENSG00000186432 KPNA4 lung macrophages Medium Enhanced O00629 3840 +ENSG00000186432 KPNA4 lung pneumocytes High Enhanced O00629 3840 +ENSG00000186439 TRDN bronchus respiratory epithelial cells Low Enhanced Q13061 10345 +ENSG00000186471 AKAP14 bronchus respiratory epithelial cells Medium Enhanced Q86UN6 158798 +ENSG00000186522 SEPT10 bronchus respiratory epithelial cells High Enhanced Q9P0V9 151011 +ENSG00000186522 SEPT10 lung macrophages Medium Enhanced Q9P0V9 151011 +ENSG00000186522 SEPT10 lung pneumocytes Medium Enhanced Q9P0V9 151011 +ENSG00000186575 NF2 bronchus respiratory epithelial cells High Supported P35240 4771 +ENSG00000186575 NF2 lung macrophages High Supported P35240 4771 +ENSG00000186575 NF2 lung pneumocytes Medium Supported P35240 4771 +ENSG00000186710 CFAP73 bronchus respiratory epithelial cells High Enhanced A6NFT4 387885 +ENSG00000186810 CXCR3 bronchus respiratory epithelial cells Low Enhanced P49682 2833 +ENSG00000186810 CXCR3 lung macrophages Low Enhanced P49682 2833 +ENSG00000186810 CXCR3 lung pneumocytes Low Enhanced P49682 2833 +ENSG00000186834 HEXIM1 bronchus respiratory epithelial cells High Supported O94992 10614 +ENSG00000186834 HEXIM1 lung macrophages High Supported O94992 10614 +ENSG00000186834 HEXIM1 lung pneumocytes High Supported O94992 10614 +ENSG00000186951 PPARA bronchus respiratory epithelial cells High Supported Q07869 5465 +ENSG00000186951 PPARA lung macrophages High Supported Q07869 5465 +ENSG00000186951 PPARA lung pneumocytes High Supported Q07869 5465 +ENSG00000187094 CCK bronchus respiratory epithelial cells Low Enhanced P06307 885 +ENSG00000187097 ENTPD5 bronchus respiratory epithelial cells Medium Enhanced O75356 957 +ENSG00000187097 ENTPD5 lung macrophages Low Enhanced O75356 957 +ENSG00000187098 MITF lung macrophages Low Enhanced O75030 4286 +ENSG00000187239 FNBP1 lung macrophages Medium Enhanced Q96RU3 23048 +ENSG00000187492 CDHR4 bronchus respiratory epithelial cells Medium Enhanced A6H8M9 389118 +ENSG00000187531 SIRT7 bronchus respiratory epithelial cells Medium Enhanced Q9NRC8 51547 +ENSG00000187678 SPRY4 bronchus respiratory epithelial cells High Enhanced Q9C004 81848 +ENSG00000187678 SPRY4 lung macrophages High Enhanced Q9C004 81848 +ENSG00000187678 SPRY4 lung pneumocytes Low Enhanced Q9C004 81848 +ENSG00000187726 DNAJB13 bronchus respiratory epithelial cells Medium Enhanced P59910 374407 +ENSG00000187778 MCRS1 bronchus respiratory epithelial cells Medium Supported Q96EZ8 10445 +ENSG00000187778 MCRS1 lung macrophages Medium Supported Q96EZ8 10445 +ENSG00000187778 MCRS1 lung pneumocytes High Supported Q96EZ8 10445 +ENSG00000187837 HIST1H1C bronchus respiratory epithelial cells High Supported P16403 3006 +ENSG00000187837 HIST1H1C lung macrophages Medium Supported P16403 3006 +ENSG00000187837 HIST1H1C lung pneumocytes High Supported P16403 3006 +ENSG00000187838 PLSCR3 bronchus respiratory epithelial cells High Supported Q8WYZ0 NA +ENSG00000187838 PLSCR3 lung macrophages Medium Supported Q8WYZ0 NA +ENSG00000187838 PLSCR3 lung pneumocytes Low Supported Q8WYZ0 NA +ENSG00000187840 EIF4EBP1 bronchus respiratory epithelial cells Low Supported Q13541 1978 +ENSG00000187840 EIF4EBP1 lung macrophages Medium Supported Q13541 1978 +ENSG00000187840 EIF4EBP1 lung pneumocytes Low Supported Q13541 1978 +ENSG00000187867 PALM3 lung macrophages Medium Enhanced A6NDB9 342979 +ENSG00000187867 PALM3 lung pneumocytes Low Enhanced A6NDB9 342979 +ENSG00000187908 DMBT1 lung macrophages Medium Enhanced Q9UGM3 1755 +ENSG00000187908 DMBT1 lung pneumocytes Medium Enhanced Q9UGM3 1755 +ENSG00000188021 UBQLN2 bronchus respiratory epithelial cells Medium Enhanced Q9UHD9 29978 +ENSG00000188021 UBQLN2 lung macrophages Medium Enhanced Q9UHD9 29978 +ENSG00000188021 UBQLN2 lung pneumocytes Medium Enhanced Q9UHD9 29978 +ENSG00000188112 C6orf132 bronchus respiratory epithelial cells Medium Enhanced Q5T0Z8 647024 +ENSG00000188186 LAMTOR4 bronchus respiratory epithelial cells Medium Enhanced Q0VGL1 389541 +ENSG00000188186 LAMTOR4 lung macrophages Medium Enhanced Q0VGL1 389541 +ENSG00000188229 TUBB4B bronchus respiratory epithelial cells High Enhanced P68371 10383 +ENSG00000188229 TUBB4B lung macrophages Low Enhanced P68371 10383 +ENSG00000188229 TUBB4B lung pneumocytes Low Enhanced P68371 10383 +ENSG00000188316 ENO4 bronchus respiratory epithelial cells High Enhanced A6NNW6 NA +ENSG00000188342 GTF2F2 bronchus respiratory epithelial cells High Supported P13984 2963 +ENSG00000188342 GTF2F2 lung macrophages High Supported P13984 2963 +ENSG00000188342 GTF2F2 lung pneumocytes Medium Supported P13984 2963 +ENSG00000188343 FAM92A bronchus respiratory epithelial cells Low Enhanced A1XBS5 137392 +ENSG00000188375 H3F3C bronchus respiratory epithelial cells High Supported Q6NXT2 440093 +ENSG00000188375 H3F3C lung macrophages Medium Supported Q6NXT2 440093 +ENSG00000188375 H3F3C lung pneumocytes High Supported Q6NXT2 440093 +ENSG00000188396 TCTEX1D4 bronchus respiratory epithelial cells Medium Enhanced Q5JR98 343521 +ENSG00000188486 H2AFX bronchus respiratory epithelial cells Medium Supported P16104 3014 +ENSG00000188486 H2AFX lung macrophages High Supported P16104 3014 +ENSG00000188486 H2AFX lung pneumocytes High Supported P16104 3014 +ENSG00000188487 INSC lung macrophages Low Enhanced Q1MX18 387755 +ENSG00000188487 INSC lung pneumocytes Low Enhanced Q1MX18 387755 +ENSG00000188522 FAM83G lung macrophages Medium Enhanced A6ND36 644815 +ENSG00000188522 FAM83G lung pneumocytes Low Enhanced A6ND36 644815 +ENSG00000188523 CFAP77 bronchus respiratory epithelial cells Medium Enhanced Q6ZQR2 389799 +ENSG00000188596 CFAP54 bronchus respiratory epithelial cells Medium Enhanced Q96N23 144535 +ENSG00000188612 SUMO2 bronchus respiratory epithelial cells High Enhanced P61956 6613 +ENSG00000188612 SUMO2 lung macrophages Medium Enhanced P61956 6613 +ENSG00000188612 SUMO2 lung pneumocytes High Enhanced P61956 6613 +ENSG00000188643 S100A16 bronchus respiratory epithelial cells Medium Enhanced Q96FQ6 140576 +ENSG00000188659 SAXO2 bronchus respiratory epithelial cells High Enhanced Q658L1 283726 +ENSG00000188732 FAM221A bronchus respiratory epithelial cells Medium Enhanced A4D161 340277 +ENSG00000188732 FAM221A lung macrophages Medium Enhanced A4D161 340277 +ENSG00000188732 FAM221A lung pneumocytes High Enhanced A4D161 340277 +ENSG00000188817 SNTN bronchus respiratory epithelial cells High Enhanced A6NMZ2 132203 +ENSG00000188931 CFAP126 bronchus respiratory epithelial cells Medium Enhanced Q5VTH2 257177 +ENSG00000188986 NELFB bronchus respiratory epithelial cells High Enhanced Q8WX92 25920 +ENSG00000188986 NELFB lung macrophages Low Enhanced Q8WX92 25920 +ENSG00000188986 NELFB lung pneumocytes Medium Enhanced Q8WX92 25920 +ENSG00000189058 APOD bronchus respiratory epithelial cells High Enhanced P05090 347 +ENSG00000189058 APOD lung macrophages Medium Enhanced P05090 347 +ENSG00000189060 H1F0 bronchus respiratory epithelial cells High Enhanced P07305 3005 +ENSG00000189060 H1F0 lung macrophages Medium Enhanced P07305 3005 +ENSG00000189060 H1F0 lung pneumocytes High Enhanced P07305 3005 +ENSG00000189091 SF3B3 bronchus respiratory epithelial cells High Supported Q15393 23450 +ENSG00000189091 SF3B3 lung macrophages Medium Supported Q15393 23450 +ENSG00000189091 SF3B3 lung pneumocytes Medium Supported Q15393 23450 +ENSG00000189143 CLDN4 bronchus respiratory epithelial cells Medium Enhanced O14493 1364 +ENSG00000189143 CLDN4 lung pneumocytes Medium Enhanced O14493 1364 +ENSG00000189221 MAOA bronchus respiratory epithelial cells Low Enhanced P21397 4128 +ENSG00000189221 MAOA lung macrophages Low Enhanced P21397 4128 +ENSG00000189221 MAOA lung pneumocytes High Enhanced P21397 4128 +ENSG00000189283 FHIT bronchus respiratory epithelial cells Medium Enhanced P49789 2272 +ENSG00000189283 FHIT lung macrophages Medium Enhanced P49789 2272 +ENSG00000189283 FHIT lung pneumocytes Medium Enhanced P49789 2272 +ENSG00000189403 HMGB1 bronchus respiratory epithelial cells High Supported P09429 3146 +ENSG00000189403 HMGB1 lung macrophages High Supported P09429 3146 +ENSG00000189403 HMGB1 lung pneumocytes High Supported P09429 3146 +ENSG00000196126 HLA-DRB1 lung macrophages High Enhanced P04229 NA +ENSG00000196126 HLA-DRB1 lung pneumocytes Low Enhanced P04229 NA +ENSG00000196136 SERPINA3 lung macrophages Low Enhanced P01011 12 +ENSG00000196139 AKR1C3 bronchus respiratory epithelial cells Medium Enhanced P42330 8644 +ENSG00000196139 AKR1C3 lung macrophages Medium Enhanced P42330 8644 +ENSG00000196139 AKR1C3 lung pneumocytes Medium Enhanced P42330 8644 +ENSG00000196154 S100A4 lung macrophages High Enhanced P26447 6275 +ENSG00000196154 S100A4 lung pneumocytes Medium Enhanced P26447 6275 +ENSG00000196169 KIF19 bronchus respiratory epithelial cells High Enhanced Q2TAC6 124602 +ENSG00000196177 ACADSB bronchus respiratory epithelial cells Low Enhanced P45954 36 +ENSG00000196188 CTSE lung pneumocytes Low Enhanced P14091 1510 +ENSG00000196199 MPHOSPH8 bronchus respiratory epithelial cells High Enhanced Q99549 54737 +ENSG00000196199 MPHOSPH8 lung pneumocytes Medium Enhanced Q99549 54737 +ENSG00000196220 SRGAP3 bronchus respiratory epithelial cells Low Enhanced O43295 9901 +ENSG00000196230 TUBB bronchus respiratory epithelial cells High Enhanced NA NA +ENSG00000196230 TUBB lung macrophages Low Enhanced NA NA +ENSG00000196230 TUBB lung pneumocytes Low Enhanced NA NA +ENSG00000196235 SUPT5H bronchus respiratory epithelial cells Medium Enhanced O00267 6829 +ENSG00000196235 SUPT5H lung macrophages Medium Enhanced O00267 6829 +ENSG00000196235 SUPT5H lung pneumocytes Medium Enhanced O00267 6829 +ENSG00000196236 XPNPEP3 bronchus respiratory epithelial cells Medium Enhanced Q9NQH7 63929 +ENSG00000196236 XPNPEP3 lung macrophages Medium Enhanced Q9NQH7 63929 +ENSG00000196284 SUPT3H bronchus respiratory epithelial cells Medium Enhanced O75486 8464 +ENSG00000196284 SUPT3H lung macrophages Low Enhanced O75486 8464 +ENSG00000196284 SUPT3H lung pneumocytes Medium Enhanced O75486 8464 +ENSG00000196290 NIF3L1 bronchus respiratory epithelial cells High Enhanced Q9GZT8 60491 +ENSG00000196290 NIF3L1 lung macrophages Medium Enhanced Q9GZT8 60491 +ENSG00000196290 NIF3L1 lung pneumocytes Medium Enhanced Q9GZT8 60491 +ENSG00000196344 ADH7 bronchus respiratory epithelial cells High Enhanced P40394 131 +ENSG00000196352 CD55 bronchus respiratory epithelial cells Low Enhanced P08174 1604 +ENSG00000196352 CD55 lung macrophages Low Enhanced P08174 1604 +ENSG00000196352 CD55 lung pneumocytes High Enhanced P08174 1604 +ENSG00000196365 LONP1 bronchus respiratory epithelial cells High Supported P36776 9361 +ENSG00000196365 LONP1 lung macrophages High Supported P36776 9361 +ENSG00000196365 LONP1 lung pneumocytes Medium Supported P36776 9361 +ENSG00000196396 PTPN1 bronchus respiratory epithelial cells Medium Enhanced P18031 5770 +ENSG00000196396 PTPN1 lung macrophages High Enhanced P18031 5770 +ENSG00000196396 PTPN1 lung pneumocytes Medium Enhanced P18031 5770 +ENSG00000196405 EVL bronchus respiratory epithelial cells Medium Enhanced Q9UI08 51466 +ENSG00000196405 EVL lung macrophages Medium Enhanced Q9UI08 51466 +ENSG00000196419 XRCC6 bronchus respiratory epithelial cells High Enhanced P12956 2547 +ENSG00000196419 XRCC6 lung macrophages Medium Enhanced P12956 2547 +ENSG00000196419 XRCC6 lung pneumocytes High Enhanced P12956 2547 +ENSG00000196436 NPIPB15 bronchus respiratory epithelial cells High Supported A6NHN6 440348 +ENSG00000196436 NPIPB15 lung pneumocytes High Supported A6NHN6 440348 +ENSG00000196465 MYL6B bronchus respiratory epithelial cells Low Enhanced P14649 140465 +ENSG00000196465 MYL6B lung macrophages Low Enhanced P14649 140465 +ENSG00000196465 MYL6B lung pneumocytes Low Enhanced P14649 140465 +ENSG00000196466 ZNF799 bronchus respiratory epithelial cells Medium Supported Q96GE5 90576 +ENSG00000196466 ZNF799 lung macrophages Low Supported Q96GE5 90576 +ENSG00000196466 ZNF799 lung pneumocytes Low Supported Q96GE5 90576 +ENSG00000196470 SIAH1 bronchus respiratory epithelial cells Medium Enhanced Q8IUQ4 6477 +ENSG00000196470 SIAH1 lung macrophages Low Enhanced Q8IUQ4 6477 +ENSG00000196470 SIAH1 lung pneumocytes Medium Enhanced Q8IUQ4 6477 +ENSG00000196526 AFAP1 bronchus respiratory epithelial cells Low Enhanced Q8N556 60312 +ENSG00000196526 AFAP1 lung macrophages Medium Enhanced Q8N556 60312 +ENSG00000196526 AFAP1 lung pneumocytes Medium Enhanced Q8N556 60312 +ENSG00000196535 MYO18A bronchus respiratory epithelial cells Medium Enhanced Q92614 399687 +ENSG00000196535 MYO18A lung pneumocytes Low Enhanced Q92614 399687 +ENSG00000196549 MME lung macrophages Low Enhanced P08473 4311 +ENSG00000196586 MYO6 bronchus respiratory epithelial cells High Enhanced Q9UM54 4646 +ENSG00000196586 MYO6 lung pneumocytes Medium Enhanced Q9UM54 4646 +ENSG00000196591 HDAC2 bronchus respiratory epithelial cells High Supported Q92769 3066 +ENSG00000196591 HDAC2 lung macrophages High Supported Q92769 3066 +ENSG00000196591 HDAC2 lung pneumocytes High Supported Q92769 3066 +ENSG00000196616 ADH1B lung pneumocytes Low Supported P00325 125 +ENSG00000196659 TTC30B bronchus respiratory epithelial cells High Supported Q8N4P2 150737 +ENSG00000196663 TECPR2 bronchus respiratory epithelial cells Medium Enhanced O15040 9895 +ENSG00000196663 TECPR2 lung macrophages Medium Enhanced O15040 9895 +ENSG00000196663 TECPR2 lung pneumocytes Medium Enhanced O15040 9895 +ENSG00000196735 HLA-DQA1 bronchus respiratory epithelial cells Low Enhanced E9PI37 NA +ENSG00000196735 HLA-DQA1 lung macrophages High Enhanced E9PI37 NA +ENSG00000196743 GM2A lung macrophages High Enhanced P17900 2760 +ENSG00000196747 HIST1H2AI bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000196747 HIST1H2AI lung macrophages High Supported NA NA +ENSG00000196747 HIST1H2AI lung pneumocytes High Supported NA NA +ENSG00000196754 S100A2 bronchus respiratory epithelial cells High Enhanced P29034 6273 +ENSG00000196781 TLE1 bronchus respiratory epithelial cells High Supported Q04724 7088 +ENSG00000196781 TLE1 lung macrophages Medium Supported Q04724 7088 +ENSG00000196781 TLE1 lung pneumocytes High Supported Q04724 7088 +ENSG00000196787 HIST1H2AG bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000196787 HIST1H2AG lung macrophages High Supported NA NA +ENSG00000196787 HIST1H2AG lung pneumocytes High Supported NA NA +ENSG00000196812 ZSCAN16 bronchus respiratory epithelial cells High Supported Q9H4T2 80345 +ENSG00000196812 ZSCAN16 lung macrophages High Supported Q9H4T2 80345 +ENSG00000196812 ZSCAN16 lung pneumocytes High Supported Q9H4T2 80345 +ENSG00000196866 HIST1H2AD bronchus respiratory epithelial cells Medium Supported P20671 3013 +ENSG00000196866 HIST1H2AD lung macrophages High Supported P20671 3013 +ENSG00000196866 HIST1H2AD lung pneumocytes High Supported P20671 3013 +ENSG00000196878 LAMB3 bronchus respiratory epithelial cells Low Enhanced Q13751 3914 +ENSG00000196878 LAMB3 lung macrophages Low Enhanced Q13751 3914 +ENSG00000196878 LAMB3 lung pneumocytes Low Enhanced Q13751 3914 +ENSG00000196890 HIST3H2BB bronchus respiratory epithelial cells High Supported Q8N257 128312 +ENSG00000196890 HIST3H2BB lung macrophages High Supported Q8N257 128312 +ENSG00000196890 HIST3H2BB lung pneumocytes High Supported Q8N257 128312 +ENSG00000196911 KPNA5 bronchus respiratory epithelial cells Low Enhanced O15131 3841 +ENSG00000196924 FLNA lung macrophages High Enhanced P21333 2316 +ENSG00000196924 FLNA lung pneumocytes Low Enhanced P21333 2316 +ENSG00000196937 FAM3C bronchus respiratory epithelial cells High Enhanced Q92520 10447 +ENSG00000196937 FAM3C lung macrophages Medium Enhanced Q92520 10447 +ENSG00000197043 ANXA6 bronchus respiratory epithelial cells Low Enhanced P08133 309 +ENSG00000197043 ANXA6 lung macrophages Medium Enhanced P08133 309 +ENSG00000197043 ANXA6 lung pneumocytes Medium Enhanced P08133 309 +ENSG00000197061 HIST1H4C bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000197061 HIST1H4C lung pneumocytes Low Supported NA NA +ENSG00000197081 IGF2R bronchus respiratory epithelial cells Medium Supported P11717 3482 +ENSG00000197081 IGF2R lung macrophages Medium Supported P11717 3482 +ENSG00000197081 IGF2R lung pneumocytes Low Supported P11717 3482 +ENSG00000197102 DYNC1H1 bronchus respiratory epithelial cells Low Enhanced Q14204 1778 +ENSG00000197102 DYNC1H1 lung macrophages Medium Enhanced Q14204 1778 +ENSG00000197142 ACSL5 bronchus respiratory epithelial cells Low Enhanced Q9ULC5 51703 +ENSG00000197142 ACSL5 lung macrophages Low Enhanced Q9ULC5 51703 +ENSG00000197142 ACSL5 lung pneumocytes Medium Enhanced Q9ULC5 51703 +ENSG00000197153 HIST1H3J bronchus respiratory epithelial cells High Supported NA NA +ENSG00000197153 HIST1H3J lung macrophages Medium Supported NA NA +ENSG00000197153 HIST1H3J lung pneumocytes High Supported NA NA +ENSG00000197157 SND1 bronchus respiratory epithelial cells Medium Enhanced Q7KZF4 27044 +ENSG00000197157 SND1 lung macrophages Medium Enhanced Q7KZF4 27044 +ENSG00000197157 SND1 lung pneumocytes Medium Enhanced Q7KZF4 27044 +ENSG00000197168 NEK5 bronchus respiratory epithelial cells Low Enhanced Q6P3R8 341676 +ENSG00000197170 PSMD12 bronchus respiratory epithelial cells Medium Enhanced O00232 5718 +ENSG00000197170 PSMD12 lung macrophages Low Enhanced O00232 5718 +ENSG00000197183 NOL4L bronchus respiratory epithelial cells Low Enhanced Q96MY1 140688 +ENSG00000197183 NOL4L lung macrophages Medium Enhanced Q96MY1 140688 +ENSG00000197183 NOL4L lung pneumocytes Low Enhanced Q96MY1 140688 +ENSG00000197217 ENTPD4 bronchus respiratory epithelial cells High Supported Q9Y227 9583 +ENSG00000197217 ENTPD4 lung macrophages Low Supported Q9Y227 9583 +ENSG00000197238 HIST1H4J bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000197238 HIST1H4J lung pneumocytes Low Supported NA NA +ENSG00000197323 TRIM33 bronchus respiratory epithelial cells Medium Supported Q9UPN9 51592 +ENSG00000197323 TRIM33 lung macrophages Medium Supported Q9UPN9 51592 +ENSG00000197323 TRIM33 lung pneumocytes Low Supported Q9UPN9 51592 +ENSG00000197386 HTT bronchus respiratory epithelial cells Medium Enhanced P42858 3064 +ENSG00000197386 HTT lung macrophages Low Enhanced P42858 3064 +ENSG00000197386 HTT lung pneumocytes Low Enhanced P42858 3064 +ENSG00000197408 CYP2B6 bronchus respiratory epithelial cells Low Supported P20813 1555 +ENSG00000197408 CYP2B6 lung macrophages Low Supported P20813 1555 +ENSG00000197408 CYP2B6 lung pneumocytes Low Supported P20813 1555 +ENSG00000197409 HIST1H3D bronchus respiratory epithelial cells High Supported NA NA +ENSG00000197409 HIST1H3D lung macrophages Medium Supported NA NA +ENSG00000197409 HIST1H3D lung pneumocytes High Supported NA NA +ENSG00000197417 SHPK bronchus respiratory epithelial cells Medium Enhanced Q9UHJ6 23729 +ENSG00000197417 SHPK lung macrophages Medium Enhanced Q9UHJ6 23729 +ENSG00000197444 OGDHL bronchus respiratory epithelial cells Medium Enhanced Q9ULD0 55753 +ENSG00000197448 GSTK1 bronchus respiratory epithelial cells High Enhanced Q9Y2Q3 373156 +ENSG00000197448 GSTK1 lung macrophages High Enhanced Q9Y2Q3 373156 +ENSG00000197448 GSTK1 lung pneumocytes Medium Enhanced Q9Y2Q3 373156 +ENSG00000197457 STMN3 lung pneumocytes Low Enhanced Q9NZ72 50861 +ENSG00000197471 SPN lung macrophages Medium Enhanced P16150 6693 +ENSG00000197540 GZMM lung macrophages Medium Enhanced P51124 3004 +ENSG00000197548 ATG7 bronchus respiratory epithelial cells Low Supported O95352 10533 +ENSG00000197548 ATG7 lung macrophages Medium Supported O95352 10533 +ENSG00000197557 TTC30A bronchus respiratory epithelial cells Medium Supported Q86WT1 92104 +ENSG00000197579 TOPORS bronchus respiratory epithelial cells High Enhanced Q9NS56 10210 +ENSG00000197579 TOPORS lung macrophages Medium Enhanced Q9NS56 10210 +ENSG00000197579 TOPORS lung pneumocytes High Enhanced Q9NS56 10210 +ENSG00000197594 ENPP1 lung macrophages Low Enhanced P22413 5167 +ENSG00000197653 DNAH10 bronchus respiratory epithelial cells Low Enhanced Q8IVF4 196385 +ENSG00000197694 SPTAN1 bronchus respiratory epithelial cells High Enhanced Q13813 6709 +ENSG00000197694 SPTAN1 lung macrophages Low Enhanced Q13813 6709 +ENSG00000197694 SPTAN1 lung pneumocytes High Enhanced Q13813 6709 +ENSG00000197746 PSAP bronchus respiratory epithelial cells High Enhanced P07602 5660 +ENSG00000197746 PSAP lung macrophages High Enhanced P07602 5660 +ENSG00000197746 PSAP lung pneumocytes Medium Enhanced P07602 5660 +ENSG00000197747 S100A10 bronchus respiratory epithelial cells Medium Enhanced P60903 6281 +ENSG00000197747 S100A10 lung macrophages High Enhanced P60903 6281 +ENSG00000197747 S100A10 lung pneumocytes High Enhanced P60903 6281 +ENSG00000197822 OCLN bronchus respiratory epithelial cells Medium Enhanced Q16625 100506658 +ENSG00000197822 OCLN lung macrophages Low Enhanced Q16625 100506658 +ENSG00000197822 OCLN lung pneumocytes Low Enhanced Q16625 100506658 +ENSG00000197837 HIST4H4 bronchus respiratory epithelial cells High Supported NA NA +ENSG00000197837 HIST4H4 lung macrophages Low Supported NA NA +ENSG00000197837 HIST4H4 lung pneumocytes High Supported NA NA +ENSG00000197857 ZNF44 bronchus respiratory epithelial cells High Supported P15621 51710 +ENSG00000197857 ZNF44 lung macrophages High Supported P15621 51710 +ENSG00000197857 ZNF44 lung pneumocytes High Supported P15621 51710 +ENSG00000197879 MYO1C bronchus respiratory epithelial cells Medium Enhanced O00159 4641 +ENSG00000197879 MYO1C lung macrophages Medium Enhanced O00159 4641 +ENSG00000197879 MYO1C lung pneumocytes High Enhanced O00159 4641 +ENSG00000197892 KIF13B bronchus respiratory epithelial cells Medium Enhanced Q9NQT8 23303 +ENSG00000197903 HIST1H2BK bronchus respiratory epithelial cells High Supported O60814 85236 +ENSG00000197903 HIST1H2BK lung macrophages High Supported O60814 85236 +ENSG00000197903 HIST1H2BK lung pneumocytes High Supported O60814 85236 +ENSG00000197921 HES5 bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000197921 HES5 lung macrophages Medium Enhanced NA NA +ENSG00000197943 PLCG2 bronchus respiratory epithelial cells Low Enhanced P16885 5336 +ENSG00000197943 PLCG2 lung macrophages Low Enhanced P16885 5336 +ENSG00000197943 PLCG2 lung pneumocytes Low Enhanced P16885 5336 +ENSG00000197956 S100A6 bronchus respiratory epithelial cells Medium Enhanced P06703 6277 +ENSG00000197956 S100A6 lung macrophages High Enhanced P06703 6277 +ENSG00000197956 S100A6 lung pneumocytes High Enhanced P06703 6277 +ENSG00000197969 VPS13A bronchus respiratory epithelial cells Medium Enhanced Q96RL7 23230 +ENSG00000197969 VPS13A lung macrophages Medium Enhanced Q96RL7 23230 +ENSG00000197976 AKAP17A bronchus respiratory epithelial cells High Enhanced Q02040 8227 +ENSG00000197976 AKAP17A lung macrophages Medium Enhanced Q02040 8227 +ENSG00000198003 CCDC151 bronchus respiratory epithelial cells High Enhanced A5D8V7 115948 +ENSG00000198034 RPS4X bronchus respiratory epithelial cells High Supported P62701 6191 +ENSG00000198034 RPS4X lung macrophages High Supported P62701 6191 +ENSG00000198034 RPS4X lung pneumocytes Low Supported P62701 6191 +ENSG00000198053 SIRPA lung macrophages Medium Enhanced P78324 140885 +ENSG00000198087 CD2AP bronchus respiratory epithelial cells Medium Enhanced Q9Y5K6 23607 +ENSG00000198087 CD2AP lung macrophages Low Enhanced Q9Y5K6 23607 +ENSG00000198087 CD2AP lung pneumocytes Medium Enhanced Q9Y5K6 23607 +ENSG00000198113 TOR4A bronchus respiratory epithelial cells Medium Enhanced Q9NXH8 54863 +ENSG00000198113 TOR4A lung macrophages Medium Enhanced Q9NXH8 54863 +ENSG00000198113 TOR4A lung pneumocytes Low Enhanced Q9NXH8 54863 +ENSG00000198130 HIBCH bronchus respiratory epithelial cells High Enhanced Q6NVY1 26275 +ENSG00000198130 HIBCH lung macrophages Medium Enhanced Q6NVY1 26275 +ENSG00000198130 HIBCH lung pneumocytes High Enhanced Q6NVY1 26275 +ENSG00000198142 SOWAHC bronchus respiratory epithelial cells Medium Enhanced Q53LP3 65124 +ENSG00000198142 SOWAHC lung macrophages Low Enhanced Q53LP3 65124 +ENSG00000198160 MIER1 bronchus respiratory epithelial cells High Enhanced Q8N108 57708 +ENSG00000198160 MIER1 lung macrophages Low Enhanced Q8N108 57708 +ENSG00000198160 MIER1 lung pneumocytes Low Enhanced Q8N108 57708 +ENSG00000198162 MAN1A2 bronchus respiratory epithelial cells Medium Enhanced O60476 10905 +ENSG00000198162 MAN1A2 lung macrophages Low Enhanced O60476 10905 +ENSG00000198176 TFDP1 bronchus respiratory epithelial cells High Enhanced Q14186 7027 +ENSG00000198176 TFDP1 lung pneumocytes Low Enhanced Q14186 7027 +ENSG00000198231 DDX42 bronchus respiratory epithelial cells High Enhanced Q86XP3 11325 +ENSG00000198231 DDX42 lung macrophages Low Enhanced Q86XP3 11325 +ENSG00000198231 DDX42 lung pneumocytes Low Enhanced Q86XP3 11325 +ENSG00000198483 ANKRD35 bronchus respiratory epithelial cells High Enhanced Q8N283 148741 +ENSG00000198502 HLA-DRB5 lung macrophages Medium Supported Q30154 3127 +ENSG00000198502 HLA-DRB5 lung pneumocytes Low Supported Q30154 3127 +ENSG00000198513 ATL1 bronchus respiratory epithelial cells Medium Enhanced Q8WXF7 51062 +ENSG00000198513 ATL1 lung macrophages Medium Enhanced Q8WXF7 51062 +ENSG00000198513 ATL1 lung pneumocytes Low Enhanced Q8WXF7 51062 +ENSG00000198554 WDHD1 lung pneumocytes Low Enhanced O75717 11169 +ENSG00000198561 CTNND1 bronchus respiratory epithelial cells Medium Enhanced O60716 1500 +ENSG00000198561 CTNND1 lung macrophages Medium Enhanced O60716 1500 +ENSG00000198561 CTNND1 lung pneumocytes Low Enhanced O60716 1500 +ENSG00000198563 DDX39B bronchus respiratory epithelial cells High Enhanced NA NA +ENSG00000198563 DDX39B lung macrophages Medium Enhanced NA NA +ENSG00000198563 DDX39B lung pneumocytes High Enhanced NA NA +ENSG00000198604 BAZ1A bronchus respiratory epithelial cells Medium Supported Q9NRL2 11177 +ENSG00000198604 BAZ1A lung macrophages High Supported Q9NRL2 11177 +ENSG00000198604 BAZ1A lung pneumocytes High Supported Q9NRL2 11177 +ENSG00000198646 NCOA6 bronchus respiratory epithelial cells High Supported Q14686 23054 +ENSG00000198646 NCOA6 lung macrophages Medium Supported Q14686 23054 +ENSG00000198646 NCOA6 lung pneumocytes Medium Supported Q14686 23054 +ENSG00000198648 STK39 bronchus respiratory epithelial cells Medium Enhanced Q9UEW8 27347 +ENSG00000198648 STK39 lung macrophages Medium Enhanced Q9UEW8 27347 +ENSG00000198648 STK39 lung pneumocytes Low Enhanced Q9UEW8 27347 +ENSG00000198668 CALM1 bronchus respiratory epithelial cells Low Supported P0DP23 801; 805; 808 +ENSG00000198668 CALM1 lung pneumocytes Low Supported P0DP23 801; 805; 808 +ENSG00000198689 SLC9A6 bronchus respiratory epithelial cells Medium Enhanced Q92581 10479 +ENSG00000198689 SLC9A6 lung macrophages Medium Enhanced Q92581 10479 +ENSG00000198689 SLC9A6 lung pneumocytes Low Enhanced Q92581 10479 +ENSG00000198712 MT-CO2 bronchus respiratory epithelial cells High Enhanced P00403 4513 +ENSG00000198712 MT-CO2 lung macrophages Medium Enhanced P00403 4513 +ENSG00000198712 MT-CO2 lung pneumocytes Medium Enhanced P00403 4513 +ENSG00000198721 ECI2 bronchus respiratory epithelial cells Medium Enhanced O75521 10455 +ENSG00000198721 ECI2 lung macrophages Low Enhanced O75521 10455 +ENSG00000198727 MT-CYB bronchus respiratory epithelial cells Medium Enhanced P00156 4519 +ENSG00000198727 MT-CYB lung pneumocytes Low Enhanced P00156 4519 +ENSG00000198730 CTR9 bronchus respiratory epithelial cells High Enhanced Q6PD62 9646 +ENSG00000198730 CTR9 lung macrophages Medium Enhanced Q6PD62 9646 +ENSG00000198730 CTR9 lung pneumocytes Medium Enhanced Q6PD62 9646 +ENSG00000198783 ZNF830 bronchus respiratory epithelial cells High Enhanced Q96NB3 91603 +ENSG00000198783 ZNF830 lung macrophages High Enhanced Q96NB3 91603 +ENSG00000198783 ZNF830 lung pneumocytes High Enhanced Q96NB3 91603 +ENSG00000198794 SCAMP5 lung macrophages Medium Enhanced Q8TAC9 192683 +ENSG00000198795 ZNF521 bronchus respiratory epithelial cells Medium Enhanced Q96K83 25925 +ENSG00000198795 ZNF521 lung macrophages Low Enhanced Q96K83 25925 +ENSG00000198795 ZNF521 lung pneumocytes Medium Enhanced Q96K83 25925 +ENSG00000198804 MT-CO1 bronchus respiratory epithelial cells High Enhanced P00395 4512 +ENSG00000198804 MT-CO1 lung macrophages High Enhanced P00395 4512 +ENSG00000198804 MT-CO1 lung pneumocytes Low Enhanced P00395 4512 +ENSG00000198805 PNP bronchus respiratory epithelial cells Low Enhanced P00491 4860 +ENSG00000198814 GK bronchus respiratory epithelial cells Low Supported P32189 2710 +ENSG00000198814 GK lung pneumocytes Low Supported P32189 2710 +ENSG00000198821 CD247 lung pneumocytes Low Enhanced P20963 919 +ENSG00000198824 CHAMP1 bronchus respiratory epithelial cells High Enhanced Q96JM3 283489 +ENSG00000198824 CHAMP1 lung macrophages High Enhanced Q96JM3 283489 +ENSG00000198824 CHAMP1 lung pneumocytes High Enhanced Q96JM3 283489 +ENSG00000198826 ARHGAP11A bronchus respiratory epithelial cells Medium Enhanced H3BR51 NA +ENSG00000198826 ARHGAP11A lung pneumocytes Low Enhanced H3BR51 NA +ENSG00000198830 HMGN2 bronchus respiratory epithelial cells Medium Supported P05204 3151 +ENSG00000198830 HMGN2 lung macrophages Medium Supported P05204 3151 +ENSG00000198830 HMGN2 lung pneumocytes High Supported P05204 3151 +ENSG00000198833 UBE2J1 bronchus respiratory epithelial cells Low Enhanced Q9Y385 51465 +ENSG00000198833 UBE2J1 lung macrophages Low Enhanced Q9Y385 51465 +ENSG00000198833 UBE2J1 lung pneumocytes Low Enhanced Q9Y385 51465 +ENSG00000198836 OPA1 bronchus respiratory epithelial cells Medium Enhanced O60313 4976 +ENSG00000198836 OPA1 lung macrophages Medium Enhanced O60313 4976 +ENSG00000198836 OPA1 lung pneumocytes Low Enhanced O60313 4976 +ENSG00000198840 MT-ND3 bronchus respiratory epithelial cells Medium Enhanced P03897 4537 +ENSG00000198840 MT-ND3 lung macrophages Medium Enhanced P03897 4537 +ENSG00000198840 MT-ND3 lung pneumocytes Medium Enhanced P03897 4537 +ENSG00000198846 TOX bronchus respiratory epithelial cells Low Enhanced O94900 9760 +ENSG00000198846 TOX lung macrophages Medium Enhanced O94900 9760 +ENSG00000198846 TOX lung pneumocytes Low Enhanced O94900 9760 +ENSG00000198848 CES1 bronchus respiratory epithelial cells High Enhanced H3BQV8 NA +ENSG00000198848 CES1 lung macrophages High Enhanced H3BQV8 NA +ENSG00000198848 CES1 lung pneumocytes Low Enhanced H3BQV8 NA +ENSG00000198887 SMC5 bronchus respiratory epithelial cells Medium Enhanced Q8IY18 23137 +ENSG00000198887 SMC5 lung macrophages Medium Enhanced Q8IY18 23137 +ENSG00000198887 SMC5 lung pneumocytes Medium Enhanced Q8IY18 23137 +ENSG00000198900 TOP1 bronchus respiratory epithelial cells High Enhanced P11387 7150 +ENSG00000198900 TOP1 lung pneumocytes Medium Enhanced P11387 7150 +ENSG00000198901 PRC1 bronchus respiratory epithelial cells High Enhanced O43663 9055 +ENSG00000198901 PRC1 lung macrophages Medium Enhanced O43663 9055 +ENSG00000198901 PRC1 lung pneumocytes Low Enhanced O43663 9055 +ENSG00000198910 L1CAM bronchus respiratory epithelial cells Low Enhanced P32004 3897 +ENSG00000198910 L1CAM lung macrophages Low Enhanced P32004 3897 +ENSG00000198910 L1CAM lung pneumocytes Low Enhanced P32004 3897 +ENSG00000198915 RASGEF1A bronchus respiratory epithelial cells Low Enhanced Q8N9B8 221002 +ENSG00000198920 KIAA0753 bronchus respiratory epithelial cells High Enhanced Q2KHM9 9851 +ENSG00000198920 KIAA0753 lung macrophages Medium Enhanced Q2KHM9 9851 +ENSG00000198920 KIAA0753 lung pneumocytes Medium Enhanced Q2KHM9 9851 +ENSG00000198951 NAGA bronchus respiratory epithelial cells Low Enhanced P17050 4668 +ENSG00000198951 NAGA lung macrophages Medium Enhanced P17050 4668 +ENSG00000198951 NAGA lung pneumocytes Medium Enhanced P17050 4668 +ENSG00000198959 TGM2 lung macrophages Medium Enhanced P21980 7052 +ENSG00000198959 TGM2 lung pneumocytes Medium Enhanced P21980 7052 +ENSG00000198961 PJA2 bronchus respiratory epithelial cells Medium Enhanced O43164 9867 +ENSG00000198961 PJA2 lung macrophages Medium Enhanced O43164 9867 +ENSG00000198961 PJA2 lung pneumocytes Low Enhanced O43164 9867 +ENSG00000203668 CHML bronchus respiratory epithelial cells Medium Supported P26374 1122 +ENSG00000203668 CHML lung macrophages Low Supported P26374 1122 +ENSG00000203747 FCGR3A lung macrophages High Supported P08637 2214 +ENSG00000203797 DDO bronchus respiratory epithelial cells High Enhanced Q99489 8528 +ENSG00000203797 DDO lung macrophages High Enhanced Q99489 8528 +ENSG00000203797 DDO lung pneumocytes Medium Enhanced Q99489 8528 +ENSG00000203811 HIST2H3C bronchus respiratory epithelial cells High Supported NA NA +ENSG00000203811 HIST2H3C lung macrophages Medium Supported NA NA +ENSG00000203811 HIST2H3C lung pneumocytes High Supported NA NA +ENSG00000203812 HIST2H2AA3 bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000203812 HIST2H2AA3 lung macrophages High Supported NA NA +ENSG00000203812 HIST2H2AA3 lung pneumocytes High Supported NA NA +ENSG00000203814 HIST2H2BF bronchus respiratory epithelial cells High Supported Q5QNW6 440689 +ENSG00000203814 HIST2H2BF lung macrophages High Supported Q5QNW6 440689 +ENSG00000203814 HIST2H2BF lung pneumocytes High Supported Q5QNW6 440689 +ENSG00000203818 HIST2H3PS2 bronchus respiratory epithelial cells High Supported Q5TEC6 NA +ENSG00000203818 HIST2H3PS2 lung macrophages Medium Supported Q5TEC6 NA +ENSG00000203818 HIST2H3PS2 lung pneumocytes High Supported Q5TEC6 NA +ENSG00000203852 HIST2H3A bronchus respiratory epithelial cells High Supported NA NA +ENSG00000203852 HIST2H3A lung macrophages Medium Supported NA NA +ENSG00000203852 HIST2H3A lung pneumocytes High Supported NA NA +ENSG00000203879 GDI1 bronchus respiratory epithelial cells Medium Enhanced P31150 2664 +ENSG00000203879 GDI1 lung macrophages Low Enhanced P31150 2664 +ENSG00000203943 SAMD13 bronchus respiratory epithelial cells Low Enhanced Q5VXD3 148418 +ENSG00000203965 EFCAB7 bronchus respiratory epithelial cells High Enhanced A8K855 84455 +ENSG00000204052 LRRC73 bronchus respiratory epithelial cells Medium Enhanced Q5JTD7 221424 +ENSG00000204065 TCEAL5 bronchus respiratory epithelial cells High Supported Q5H9L2 340543 +ENSG00000204071 TCEAL6 bronchus respiratory epithelial cells Low Supported Q6IPX3 NA +ENSG00000204209 DAXX bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000204209 DAXX lung macrophages Medium Enhanced NA NA +ENSG00000204209 DAXX lung pneumocytes Medium Enhanced NA NA +ENSG00000204227 RING1 bronchus respiratory epithelial cells High Supported NA NA +ENSG00000204227 RING1 lung macrophages Medium Supported NA NA +ENSG00000204227 RING1 lung pneumocytes Medium Supported NA NA +ENSG00000204228 HSD17B8 bronchus respiratory epithelial cells High Enhanced NA NA +ENSG00000204228 HSD17B8 lung macrophages Medium Enhanced NA NA +ENSG00000204231 RXRB bronchus respiratory epithelial cells High Supported NA NA +ENSG00000204231 RXRB lung macrophages High Supported NA NA +ENSG00000204231 RXRB lung pneumocytes High Supported NA NA +ENSG00000204252 HLA-DOA bronchus respiratory epithelial cells Low Enhanced F6WU08 NA +ENSG00000204252 HLA-DOA lung macrophages Low Enhanced F6WU08 NA +ENSG00000204252 HLA-DOA lung pneumocytes Medium Enhanced F6WU08 NA +ENSG00000204257 HLA-DMA lung macrophages High Enhanced F6S093 NA +ENSG00000204257 HLA-DMA lung pneumocytes Low Enhanced F6S093 NA +ENSG00000204264 PSMB8 bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000204264 PSMB8 lung macrophages Medium Enhanced NA NA +ENSG00000204264 PSMB8 lung pneumocytes Medium Enhanced NA NA +ENSG00000204287 HLA-DRA bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000204287 HLA-DRA lung macrophages High Enhanced NA NA +ENSG00000204287 HLA-DRA lung pneumocytes Medium Enhanced NA NA +ENSG00000204304 PBX2 bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000204304 PBX2 lung pneumocytes Low Enhanced NA NA +ENSG00000204305 AGER lung macrophages High Enhanced NA NA +ENSG00000204305 AGER lung pneumocytes High Enhanced NA NA +ENSG00000204315 FKBPL bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000204315 FKBPL lung macrophages Low Enhanced NA NA +ENSG00000204356 NELFE bronchus respiratory epithelial cells High Enhanced E9PD43 NA +ENSG00000204356 NELFE lung macrophages High Enhanced E9PD43 NA +ENSG00000204356 NELFE lung pneumocytes High Enhanced E9PD43 NA +ENSG00000204361 NXPE2 bronchus respiratory epithelial cells Low Enhanced Q96DL1 120406 +ENSG00000204361 NXPE2 lung macrophages Low Enhanced Q96DL1 120406 +ENSG00000204371 EHMT2 bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000204385 SLC44A4 bronchus respiratory epithelial cells High Enhanced NA NA +ENSG00000204385 SLC44A4 lung macrophages Low Enhanced NA NA +ENSG00000204389 HSPA1A bronchus respiratory epithelial cells High Supported NA NA +ENSG00000204389 HSPA1A lung macrophages Medium Supported NA NA +ENSG00000204389 HSPA1A lung pneumocytes Medium Supported NA NA +ENSG00000204392 LSM2 bronchus respiratory epithelial cells High Supported NA NA +ENSG00000204392 LSM2 lung macrophages Low Supported NA NA +ENSG00000204392 LSM2 lung pneumocytes High Supported NA NA +ENSG00000204463 BAG6 bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000204463 BAG6 lung macrophages Low Enhanced NA NA +ENSG00000204463 BAG6 lung pneumocytes Low Enhanced NA NA +ENSG00000204472 AIF1 lung macrophages High Enhanced NA NA +ENSG00000204560 DHX16 bronchus respiratory epithelial cells High Enhanced NA NA +ENSG00000204560 DHX16 lung macrophages Low Enhanced NA NA +ENSG00000204560 DHX16 lung pneumocytes High Enhanced NA NA +ENSG00000204568 MRPS18B bronchus respiratory epithelial cells High Supported NA NA +ENSG00000204568 MRPS18B lung macrophages Medium Supported NA NA +ENSG00000204568 MRPS18B lung pneumocytes Medium Supported NA NA +ENSG00000204569 PPP1R10 bronchus respiratory epithelial cells High Enhanced NA NA +ENSG00000204569 PPP1R10 lung macrophages Low Enhanced NA NA +ENSG00000204569 PPP1R10 lung pneumocytes Low Enhanced NA NA +ENSG00000204592 HLA-E bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000204592 HLA-E lung macrophages Medium Enhanced NA NA +ENSG00000204592 HLA-E lung pneumocytes Medium Enhanced NA NA +ENSG00000204815 TTC25 bronchus respiratory epithelial cells High Enhanced Q96NG3 83538 +ENSG00000204842 ATXN2 bronchus respiratory epithelial cells Medium Enhanced Q99700 6311 +ENSG00000204842 ATXN2 lung macrophages Medium Enhanced Q99700 6311 +ENSG00000204851 PNMAL2 bronchus respiratory epithelial cells Medium Enhanced Q9ULN7 57469 +ENSG00000204856 FAM216A bronchus respiratory epithelial cells Low Enhanced Q8WUB2 29902 +ENSG00000204977 TRIM13 bronchus respiratory epithelial cells Medium Enhanced O60858 10206 +ENSG00000204977 TRIM13 lung macrophages Low Enhanced O60858 10206 +ENSG00000204977 TRIM13 lung pneumocytes Medium Enhanced O60858 10206 +ENSG00000205084 TMEM231 bronchus respiratory epithelial cells Medium Enhanced Q9H6L2 79583 +ENSG00000205189 ZBTB10 bronchus respiratory epithelial cells High Enhanced Q96DT7 65986 +ENSG00000205189 ZBTB10 lung macrophages High Enhanced Q96DT7 65986 +ENSG00000205189 ZBTB10 lung pneumocytes High Enhanced Q96DT7 65986 +ENSG00000205220 PSMB10 bronchus respiratory epithelial cells Medium Enhanced P40306 5699 +ENSG00000205220 PSMB10 lung macrophages Medium Enhanced P40306 5699 +ENSG00000205220 PSMB10 lung pneumocytes Medium Enhanced P40306 5699 +ENSG00000205323 SARNP bronchus respiratory epithelial cells High Supported P82979 84324 +ENSG00000205323 SARNP lung macrophages Medium Supported P82979 84324 +ENSG00000205323 SARNP lung pneumocytes High Supported P82979 84324 +ENSG00000205420 KRT6A bronchus respiratory epithelial cells Medium Supported P02538 3853 +ENSG00000205571 SMN2 bronchus respiratory epithelial cells High Supported A0A1W2PRV5 NA +ENSG00000205571 SMN2 lung macrophages Low Supported A0A1W2PRV5 NA +ENSG00000205571 SMN2 lung pneumocytes Low Supported A0A1W2PRV5 NA +ENSG00000205581 HMGN1 bronchus respiratory epithelial cells High Supported P05114 3150 +ENSG00000205581 HMGN1 lung macrophages High Supported P05114 3150 +ENSG00000205581 HMGN1 lung pneumocytes High Supported P05114 3150 +ENSG00000205609 EIF3CL bronchus respiratory epithelial cells High Supported B5ME19 728689 +ENSG00000205609 EIF3CL lung macrophages Medium Supported B5ME19 728689 +ENSG00000205609 EIF3CL lung pneumocytes Medium Supported B5ME19 728689 +ENSG00000205744 DENND1C lung macrophages Medium Enhanced Q8IV53 79958 +ENSG00000205929 C21orf62 lung macrophages Medium Enhanced NA NA +ENSG00000206073 SERPINB4 bronchus respiratory epithelial cells High Supported P48594 6318 +ENSG00000206075 SERPINB5 bronchus respiratory epithelial cells Low Enhanced P36952 5268 +ENSG00000206075 SERPINB5 lung macrophages Low Enhanced P36952 5268 +ENSG00000206075 SERPINB5 lung pneumocytes Low Enhanced P36952 5268 +ENSG00000212719 C17orf51 bronchus respiratory epithelial cells High Enhanced A8MQB3 339263 +ENSG00000212719 C17orf51 lung macrophages Low Enhanced A8MQB3 339263 +ENSG00000213024 NUP62 bronchus respiratory epithelial cells Low Enhanced P37198 23636 +ENSG00000213024 NUP62 lung macrophages Medium Enhanced P37198 23636 +ENSG00000213024 NUP62 lung pneumocytes Low Enhanced P37198 23636 +ENSG00000213079 SCAF8 bronchus respiratory epithelial cells High Enhanced Q9UPN6 22828 +ENSG00000213079 SCAF8 lung macrophages High Enhanced Q9UPN6 22828 +ENSG00000213079 SCAF8 lung pneumocytes High Enhanced Q9UPN6 22828 +ENSG00000213085 CFAP45 bronchus respiratory epithelial cells High Enhanced Q9UL16 25790 +ENSG00000213185 FAM24B bronchus respiratory epithelial cells High Supported Q8N5W8 196792 +ENSG00000213214 ARHGEF35 bronchus respiratory epithelial cells Medium Supported A5YM69 445328 +ENSG00000213214 ARHGEF35 lung pneumocytes Low Supported A5YM69 445328 +ENSG00000213445 SIPA1 bronchus respiratory epithelial cells Low Enhanced Q96FS4 6494 +ENSG00000213445 SIPA1 lung macrophages Low Enhanced Q96FS4 6494 +ENSG00000213462 ERV3-1 bronchus respiratory epithelial cells Medium Enhanced Q14264 2086 +ENSG00000213462 ERV3-1 lung macrophages Medium Enhanced Q14264 2086 +ENSG00000213462 ERV3-1 lung pneumocytes Low Enhanced Q14264 2086 +ENSG00000213465 ARL2 bronchus respiratory epithelial cells Medium Supported P36404 402 +ENSG00000213465 ARL2 lung macrophages Medium Supported P36404 402 +ENSG00000213465 ARL2 lung pneumocytes Medium Supported P36404 402 +ENSG00000213516 RBMXL1 bronchus respiratory epithelial cells High Supported Q96E39 494115 +ENSG00000213516 RBMXL1 lung macrophages Medium Supported Q96E39 494115 +ENSG00000213516 RBMXL1 lung pneumocytes High Supported Q96E39 494115 +ENSG00000213551 DNAJC9 bronchus respiratory epithelial cells High Enhanced Q8WXX5 23234 +ENSG00000213551 DNAJC9 lung macrophages Medium Enhanced Q8WXX5 23234 +ENSG00000213551 DNAJC9 lung pneumocytes Medium Enhanced Q8WXX5 23234 +ENSG00000213585 VDAC1 bronchus respiratory epithelial cells Medium Supported P21796 7416 +ENSG00000213585 VDAC1 lung macrophages High Supported P21796 7416 +ENSG00000213585 VDAC1 lung pneumocytes Low Supported P21796 7416 +ENSG00000213614 HEXA bronchus respiratory epithelial cells Low Supported P06865 3073 +ENSG00000213614 HEXA lung macrophages High Supported P06865 3073 +ENSG00000213639 PPP1CB bronchus respiratory epithelial cells Medium Supported P62140 5500 +ENSG00000213639 PPP1CB lung macrophages Medium Supported P62140 5500 +ENSG00000213689 TREX1 bronchus respiratory epithelial cells Medium Supported Q9NSU2 11277 +ENSG00000213689 TREX1 lung macrophages Medium Supported Q9NSU2 11277 +ENSG00000213689 TREX1 lung pneumocytes Low Supported Q9NSU2 11277 +ENSG00000213719 CLIC1 bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000213719 CLIC1 lung macrophages Low Enhanced NA NA +ENSG00000213719 CLIC1 lung pneumocytes Low Enhanced NA NA +ENSG00000213762 ZNF134 bronchus respiratory epithelial cells Medium Supported P52741 7693 +ENSG00000213762 ZNF134 lung pneumocytes Medium Supported P52741 7693 +ENSG00000213918 DNASE1 bronchus respiratory epithelial cells Low Enhanced P24855 1773 +ENSG00000213930 GALT bronchus respiratory epithelial cells Medium Enhanced P07902 2592 +ENSG00000213930 GALT lung macrophages Medium Enhanced P07902 2592 +ENSG00000213930 GALT lung pneumocytes Medium Enhanced P07902 2592 +ENSG00000214114 MYCBP bronchus respiratory epithelial cells High Supported Q99417 26292 +ENSG00000214114 MYCBP lung pneumocytes Low Supported Q99417 26292 +ENSG00000214279 SCART1 lung macrophages Low Supported NA NA +ENSG00000214753 HNRNPUL2 bronchus respiratory epithelial cells Low Enhanced Q1KMD3 221092 +ENSG00000214753 HNRNPUL2 lung macrophages Medium Enhanced Q1KMD3 221092 +ENSG00000214753 HNRNPUL2 lung pneumocytes Low Enhanced Q1KMD3 221092 +ENSG00000214944 ARHGEF28 bronchus respiratory epithelial cells Low Enhanced Q8N1W1 64283 +ENSG00000214944 ARHGEF28 lung macrophages Low Enhanced Q8N1W1 64283 +ENSG00000215021 PHB2 bronchus respiratory epithelial cells High Supported Q99623 11331 +ENSG00000215021 PHB2 lung macrophages Medium Supported Q99623 11331 +ENSG00000215021 PHB2 lung pneumocytes Medium Supported Q99623 11331 +ENSG00000215182 MUC5AC bronchus respiratory epithelial cells High Enhanced NA NA +ENSG00000215187 FAM166B bronchus respiratory epithelial cells High Enhanced A8MTA8 730112 +ENSG00000215217 C5orf49 bronchus respiratory epithelial cells Medium Enhanced A4QMS7 134121 +ENSG00000215301 DDX3X bronchus respiratory epithelial cells High Supported O00571 1654 +ENSG00000215301 DDX3X lung macrophages Medium Supported O00571 1654 +ENSG00000215301 DDX3X lung pneumocytes High Supported O00571 1654 +ENSG00000221978 CCNL2 bronchus respiratory epithelial cells Medium Supported Q96S94 81669 +ENSG00000221978 CCNL2 lung macrophages Medium Supported Q96S94 81669 +ENSG00000221978 CCNL2 lung pneumocytes Medium Supported Q96S94 81669 +ENSG00000221983 UBA52 bronchus respiratory epithelial cells High Supported P62987 7311 +ENSG00000221983 UBA52 lung macrophages Medium Supported P62987 7311 +ENSG00000221983 UBA52 lung pneumocytes Medium Supported P62987 7311 +ENSG00000221994 ZNF630 bronchus respiratory epithelial cells High Supported Q2M218 57232 +ENSG00000221994 ZNF630 lung pneumocytes Medium Supported Q2M218 57232 +ENSG00000223609 HBD lung macrophages Low Supported P02042 3045 +ENSG00000223609 HBD lung pneumocytes Low Supported P02042 3045 +ENSG00000225921 NOL7 bronchus respiratory epithelial cells Low Supported Q9UMY1 51406 +ENSG00000225921 NOL7 lung macrophages Low Supported Q9UMY1 51406 +ENSG00000226321 CROCC2 bronchus respiratory epithelial cells High Enhanced H7BZ55 NA +ENSG00000226372 DCAF8L1 bronchus respiratory epithelial cells Low Enhanced A6NGE4 139425 +ENSG00000230873 STMND1 bronchus respiratory epithelial cells High Enhanced H3BQB6 401236 +ENSG00000231389 HLA-DPA1 bronchus respiratory epithelial cells Low Enhanced J3KQ99 NA +ENSG00000231389 HLA-DPA1 lung macrophages Medium Enhanced J3KQ99 NA +ENSG00000232070 TMEM253 bronchus respiratory epithelial cells Low Enhanced P0C7T8 643382 +ENSG00000233822 HIST1H2BN bronchus respiratory epithelial cells High Supported Q99877 8341 +ENSG00000233822 HIST1H2BN lung macrophages High Supported Q99877 8341 +ENSG00000233822 HIST1H2BN lung pneumocytes High Supported Q99877 8341 +ENSG00000234289 H2BFS bronchus respiratory epithelial cells High Supported P57053 102724334 +ENSG00000234289 H2BFS lung macrophages High Supported P57053 102724334 +ENSG00000234289 H2BFS lung pneumocytes High Supported P57053 102724334 +ENSG00000234719 NPIPB2 bronchus respiratory epithelial cells Medium Supported F8VY45 NA +ENSG00000234719 NPIPB2 lung macrophages Medium Supported F8VY45 NA +ENSG00000234719 NPIPB2 lung pneumocytes Medium Supported F8VY45 NA +ENSG00000234745 HLA-B bronchus respiratory epithelial cells High Enhanced P01889 3106 +ENSG00000234745 HLA-B lung macrophages Medium Enhanced P01889 3106 +ENSG00000234745 HLA-B lung pneumocytes High Enhanced P01889 3106 +ENSG00000235098 ANKRD65 bronchus respiratory epithelial cells Medium Enhanced E5RJM6 441869 +ENSG00000237649 KIFC1 bronchus respiratory epithelial cells Low Supported A0A087X1W5 NA +ENSG00000238227 C9orf69 bronchus respiratory epithelial cells High Supported H0YL14 90120 +ENSG00000238227 C9orf69 lung macrophages High Supported H0YL14 90120 +ENSG00000238227 C9orf69 lung pneumocytes High Supported H0YL14 90120 +ENSG00000239264 TXNDC5 lung pneumocytes Low Enhanced Q8NBS9 81567 +ENSG00000239306 RBM14 bronchus respiratory epithelial cells High Supported Q96PK6 100526737; 10432 +ENSG00000239306 RBM14 lung macrophages High Supported Q96PK6 100526737; 10432 +ENSG00000239306 RBM14 lung pneumocytes High Supported Q96PK6 100526737; 10432 +ENSG00000239672 NME1 bronchus respiratory epithelial cells Medium Supported P15531 4830 +ENSG00000239672 NME1 lung macrophages Low Supported P15531 4830 +ENSG00000239672 NME1 lung pneumocytes Low Supported P15531 4830 +ENSG00000239900 ADSL bronchus respiratory epithelial cells High Enhanced P30566 158 +ENSG00000239900 ADSL lung macrophages Medium Enhanced P30566 158 +ENSG00000239900 ADSL lung pneumocytes Medium Enhanced P30566 158 +ENSG00000240065 PSMB9 bronchus respiratory epithelial cells Low Enhanced NA NA +ENSG00000240065 PSMB9 lung macrophages Medium Enhanced NA NA +ENSG00000240065 PSMB9 lung pneumocytes Low Enhanced NA NA +ENSG00000240583 AQP1 lung pneumocytes Low Enhanced P29972 358 +ENSG00000240682 ISY1 bronchus respiratory epithelial cells High Supported Q9ULR0 100534599; 57461 +ENSG00000240682 ISY1 lung macrophages High Supported Q9ULR0 100534599; 57461 +ENSG00000240682 ISY1 lung pneumocytes High Supported Q9ULR0 100534599; 57461 +ENSG00000241837 ATP5O bronchus respiratory epithelial cells Medium Enhanced P48047 539 +ENSG00000241837 ATP5O lung macrophages Medium Enhanced P48047 539 +ENSG00000241837 ATP5O lung pneumocytes Low Enhanced P48047 539 +ENSG00000242110 AMACR bronchus respiratory epithelial cells Low Enhanced Q9UHK6 23600 +ENSG00000242110 AMACR lung macrophages Low Enhanced Q9UHK6 23600 +ENSG00000242372 EIF6 lung macrophages Medium Enhanced P56537 3692 +ENSG00000242372 EIF6 lung pneumocytes Low Enhanced P56537 3692 +ENSG00000242485 MRPL20 bronchus respiratory epithelial cells High Supported Q9BYC9 55052 +ENSG00000242485 MRPL20 lung macrophages High Supported Q9BYC9 55052 +ENSG00000242574 HLA-DMB lung macrophages Medium Supported H0Y7A2 NA +ENSG00000242802 AP5Z1 bronchus respiratory epithelial cells Medium Supported O43299 9907 +ENSG00000242802 AP5Z1 lung macrophages Medium Supported O43299 9907 +ENSG00000242802 AP5Z1 lung pneumocytes Medium Supported O43299 9907 +ENSG00000243279 PRAF2 bronchus respiratory epithelial cells Low Enhanced O60831 11230 +ENSG00000243279 PRAF2 lung macrophages Low Enhanced O60831 11230 +ENSG00000243279 PRAF2 lung pneumocytes Low Enhanced O60831 11230 +ENSG00000243649 CFB bronchus respiratory epithelial cells Low Supported H7C526 NA +ENSG00000243649 CFB lung macrophages Low Supported H7C526 NA +ENSG00000243710 CFAP57 bronchus respiratory epithelial cells High Enhanced Q96MR6 149465 +ENSG00000243927 MRPS6 bronchus respiratory epithelial cells High Supported P82932 64968 +ENSG00000243927 MRPS6 lung macrophages High Supported P82932 64968 +ENSG00000243927 MRPS6 lung pneumocytes High Supported P82932 64968 +ENSG00000243955 GSTA1 bronchus respiratory epithelial cells Medium Supported P08263 2938 +ENSG00000244005 NFS1 bronchus respiratory epithelial cells High Enhanced Q9Y697 9054 +ENSG00000244005 NFS1 lung pneumocytes Medium Enhanced Q9Y697 9054 +ENSG00000244038 DDOST bronchus respiratory epithelial cells High Supported P39656 1650 +ENSG00000244038 DDOST lung macrophages Medium Supported P39656 1650 +ENSG00000244038 DDOST lung pneumocytes Medium Supported P39656 1650 +ENSG00000244067 GSTA2 bronchus respiratory epithelial cells Low Supported P09210 2939 +ENSG00000244274 DBNDD2 bronchus respiratory epithelial cells Low Enhanced Q9BQY9 55861 +ENSG00000244274 DBNDD2 lung macrophages Medium Enhanced Q9BQY9 55861 +ENSG00000244462 RBM12 bronchus respiratory epithelial cells High Enhanced Q9NTZ6 10137 +ENSG00000244462 RBM12 lung macrophages Medium Enhanced Q9NTZ6 10137 +ENSG00000244462 RBM12 lung pneumocytes Medium Enhanced Q9NTZ6 10137 +ENSG00000246705 H2AFJ bronchus respiratory epithelial cells Medium Supported Q9BTM1 55766 +ENSG00000246705 H2AFJ lung macrophages High Supported Q9BTM1 55766 +ENSG00000246705 H2AFJ lung pneumocytes High Supported Q9BTM1 55766 +ENSG00000247077 PGAM5 bronchus respiratory epithelial cells Medium Enhanced Q96HS1 192111 +ENSG00000247077 PGAM5 lung macrophages Medium Enhanced Q96HS1 192111 +ENSG00000247077 PGAM5 lung pneumocytes Low Enhanced Q96HS1 192111 +ENSG00000248098 BCKDHA bronchus respiratory epithelial cells High Supported P12694 593 +ENSG00000248098 BCKDHA lung macrophages Medium Supported P12694 593 +ENSG00000248098 BCKDHA lung pneumocytes High Supported P12694 593 +ENSG00000248144 ADH1C lung macrophages Low Supported P00326 126 +ENSG00000248144 ADH1C lung pneumocytes Low Supported P00326 126 +ENSG00000248485 PCP4L1 bronchus respiratory epithelial cells Medium Enhanced A6NKN8 654790 +ENSG00000248485 PCP4L1 lung macrophages Low Enhanced A6NKN8 654790 +ENSG00000249242 TMEM150C lung macrophages Low Enhanced B9EJG8 441027 +ENSG00000250479 CHCHD10 lung macrophages Low Enhanced NA NA +ENSG00000251322 SHANK3 bronchus respiratory epithelial cells Medium Enhanced A0A0U1RR93 NA +ENSG00000251322 SHANK3 lung pneumocytes Medium Enhanced A0A0U1RR93 NA +ENSG00000253729 PRKDC bronchus respiratory epithelial cells High Supported P78527 5591 +ENSG00000253729 PRKDC lung macrophages High Supported P78527 5591 +ENSG00000253729 PRKDC lung pneumocytes High Supported P78527 5591 +ENSG00000254087 LYN bronchus respiratory epithelial cells Low Enhanced P07948 4067 +ENSG00000254087 LYN lung macrophages Low Enhanced P07948 4067 +ENSG00000254402 LRRC24 bronchus respiratory epithelial cells High Enhanced Q50LG9 441381 +ENSG00000254772 EEF1G bronchus respiratory epithelial cells Low Enhanced P26641 1937 +ENSG00000254772 EEF1G lung macrophages Low Enhanced P26641 1937 +ENSG00000255112 CHMP1B bronchus respiratory epithelial cells High Enhanced Q7LBR1 57132 +ENSG00000255112 CHMP1B lung macrophages Medium Enhanced Q7LBR1 57132 +ENSG00000255112 CHMP1B lung pneumocytes Medium Enhanced Q7LBR1 57132 +ENSG00000256269 HMBS bronchus respiratory epithelial cells Medium Enhanced A0A1W2PNU5 NA +ENSG00000256269 HMBS lung macrophages Medium Enhanced A0A1W2PNU5 NA +ENSG00000256269 HMBS lung pneumocytes Medium Enhanced A0A1W2PNU5 NA +ENSG00000257727 CNPY2 bronchus respiratory epithelial cells Medium Supported Q9Y2B0 10330 +ENSG00000257727 CNPY2 lung macrophages Medium Supported Q9Y2B0 10330 +ENSG00000257727 CNPY2 lung pneumocytes Low Supported Q9Y2B0 10330 +ENSG00000258315 C17orf49 bronchus respiratory epithelial cells High Supported Q8IXM2 124944 +ENSG00000258315 C17orf49 lung macrophages High Supported Q8IXM2 124944 +ENSG00000258315 C17orf49 lung pneumocytes High Supported Q8IXM2 124944 +ENSG00000260314 MRC1 lung macrophages High Enhanced P22897 4360 +ENSG00000261371 PECAM1 lung macrophages Low Supported P16284 5175 +ENSG00000262814 MRPL12 bronchus respiratory epithelial cells High Supported P52815 6182 +ENSG00000262814 MRPL12 lung macrophages High Supported P52815 6182 +ENSG00000262814 MRPL12 lung pneumocytes Medium Supported P52815 6182 +ENSG00000263001 GTF2I bronchus respiratory epithelial cells High Supported P78347 2969 +ENSG00000263001 GTF2I lung macrophages Low Supported P78347 2969 +ENSG00000263001 GTF2I lung pneumocytes Medium Supported P78347 2969 +ENSG00000263465 SRSF8 bronchus respiratory epithelial cells High Supported Q9BRL6 10929 +ENSG00000263465 SRSF8 lung macrophages High Supported Q9BRL6 10929 +ENSG00000263465 SRSF8 lung pneumocytes High Supported Q9BRL6 10929 +ENSG00000263639 MSMB bronchus respiratory epithelial cells Low Enhanced P08118 4477 +ENSG00000264522 OTUD7B bronchus respiratory epithelial cells Medium Supported Q6GQQ9 56957 +ENSG00000264522 OTUD7B lung macrophages Medium Supported Q6GQQ9 56957 +ENSG00000264522 OTUD7B lung pneumocytes Medium Supported Q6GQQ9 56957 +ENSG00000265241 RBM8A bronchus respiratory epithelial cells High Supported Q9Y5S9 9939 +ENSG00000265241 RBM8A lung macrophages Low Supported Q9Y5S9 9939 +ENSG00000265241 RBM8A lung pneumocytes Medium Supported Q9Y5S9 9939 +ENSG00000265681 RPL17 bronchus respiratory epithelial cells High Supported P18621 6139 +ENSG00000265681 RPL17 lung macrophages Medium Supported P18621 6139 +ENSG00000266967 AARSD1 bronchus respiratory epithelial cells Low Supported L7N2F4 NA +ENSG00000266967 AARSD1 lung macrophages Low Supported L7N2F4 NA +ENSG00000267368 UPK3BL lung macrophages Low Supported B0FP48 100134938; 107983993 +ENSG00000267855 NDUFA7 bronchus respiratory epithelial cells High Enhanced O95182 4701 +ENSG00000267855 NDUFA7 lung macrophages Medium Enhanced O95182 4701 +ENSG00000267855 NDUFA7 lung pneumocytes Medium Enhanced O95182 4701 +ENSG00000268861 CTD-2207O23.3 bronchus respiratory epithelial cells Medium Supported A0A087WZG4 NA +ENSG00000268861 CTD-2207O23.3 lung macrophages Medium Supported A0A087WZG4 NA +ENSG00000268861 CTD-2207O23.3 lung pneumocytes Low Supported A0A087WZG4 NA +ENSG00000270276 HIST2H4B bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000270276 HIST2H4B lung pneumocytes Low Supported NA NA +ENSG00000270647 TAF15 lung macrophages High Enhanced NA NA +ENSG00000270647 TAF15 lung pneumocytes Medium Enhanced NA NA +ENSG00000270765 GAS2L2 bronchus respiratory epithelial cells High Enhanced Q8NHY3 246176 +ENSG00000270882 HIST2H4A bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000270882 HIST2H4A lung pneumocytes Low Supported NA NA +ENSG00000272196 HIST2H2AA4 bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000272196 HIST2H2AA4 lung macrophages High Supported NA NA +ENSG00000272196 HIST2H2AA4 lung pneumocytes High Supported NA NA +ENSG00000273542 HIST1H4K bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000273542 HIST1H4K lung pneumocytes Low Supported NA NA +ENSG00000273559 CWC25 bronchus respiratory epithelial cells High Enhanced NA NA +ENSG00000273559 CWC25 lung pneumocytes Medium Enhanced NA NA +ENSG00000273703 HIST1H2BM bronchus respiratory epithelial cells High Supported Q99879 8342 +ENSG00000273703 HIST1H2BM lung macrophages High Supported Q99879 8342 +ENSG00000273703 HIST1H2BM lung pneumocytes High Supported Q99879 8342 +ENSG00000273802 HIST1H2BG bronchus respiratory epithelial cells High Supported NA NA +ENSG00000273802 HIST1H2BG lung macrophages High Supported NA NA +ENSG00000273802 HIST1H2BG lung pneumocytes High Supported NA NA +ENSG00000273983 HIST1H3G bronchus respiratory epithelial cells High Supported NA NA +ENSG00000273983 HIST1H3G lung macrophages Medium Supported NA NA +ENSG00000273983 HIST1H3G lung pneumocytes High Supported NA NA +ENSG00000274267 HIST1H3B bronchus respiratory epithelial cells High Supported NA NA +ENSG00000274267 HIST1H3B lung macrophages Medium Supported NA NA +ENSG00000274267 HIST1H3B lung pneumocytes High Supported NA NA +ENSG00000274290 HIST1H2BE bronchus respiratory epithelial cells High Supported NA NA +ENSG00000274290 HIST1H2BE lung macrophages High Supported NA NA +ENSG00000274290 HIST1H2BE lung pneumocytes High Supported NA NA +ENSG00000274618 HIST1H4F bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000274618 HIST1H4F lung pneumocytes Low Supported NA NA +ENSG00000274641 HIST1H2BO bronchus respiratory epithelial cells High Supported P23527 8348 +ENSG00000274641 HIST1H2BO lung macrophages High Supported P23527 8348 +ENSG00000274641 HIST1H2BO lung pneumocytes High Supported P23527 8348 +ENSG00000274750 HIST1H3E bronchus respiratory epithelial cells High Supported NA NA +ENSG00000274750 HIST1H3E lung macrophages Medium Supported NA NA +ENSG00000274750 HIST1H3E lung pneumocytes High Supported NA NA +ENSG00000274997 HIST1H2AH bronchus respiratory epithelial cells Medium Supported Q96KK5 85235 +ENSG00000274997 HIST1H2AH lung macrophages High Supported Q96KK5 85235 +ENSG00000274997 HIST1H2AH lung pneumocytes High Supported Q96KK5 85235 +ENSG00000275126 HIST1H4L bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000275126 HIST1H4L lung pneumocytes Low Supported NA NA +ENSG00000275183 LENG9 bronchus respiratory epithelial cells Medium Enhanced NA NA +ENSG00000275221 HIST1H2AK bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000275221 HIST1H2AK lung macrophages High Supported NA NA +ENSG00000275221 HIST1H2AK lung pneumocytes High Supported NA NA +ENSG00000275379 HIST1H3I bronchus respiratory epithelial cells High Supported NA NA +ENSG00000275379 HIST1H3I lung macrophages Medium Supported NA NA +ENSG00000275379 HIST1H3I lung pneumocytes High Supported NA NA +ENSG00000275395 FCGBP bronchus respiratory epithelial cells Low Enhanced A0A087WXI2 NA +ENSG00000275410 HNF1B lung pneumocytes Low Enhanced NA NA +ENSG00000275663 HIST1H4G bronchus respiratory epithelial cells Medium Supported Q99525 8369 +ENSG00000275663 HIST1H4G lung pneumocytes Low Supported Q99525 8369 +ENSG00000275713 HIST1H2BH bronchus respiratory epithelial cells High Supported Q93079 8345 +ENSG00000275713 HIST1H2BH lung macrophages High Supported Q93079 8345 +ENSG00000275713 HIST1H2BH lung pneumocytes High Supported Q93079 8345 +ENSG00000275714 HIST1H3A bronchus respiratory epithelial cells High Supported NA NA +ENSG00000275714 HIST1H3A lung macrophages Medium Supported NA NA +ENSG00000275714 HIST1H3A lung pneumocytes High Supported NA NA +ENSG00000275835 TUBGCP5 bronchus respiratory epithelial cells Medium Supported Q96RT8 114791 +ENSG00000275835 TUBGCP5 lung macrophages High Supported Q96RT8 114791 +ENSG00000275895 U2AF1L5 bronchus respiratory epithelial cells High Supported P0DN76 102724594; 7307 +ENSG00000275895 U2AF1L5 lung macrophages High Supported P0DN76 102724594; 7307 +ENSG00000275895 U2AF1L5 lung pneumocytes High Supported P0DN76 102724594; 7307 +ENSG00000276180 HIST1H4I bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000276180 HIST1H4I lung pneumocytes Low Supported NA NA +ENSG00000276368 HIST1H2AJ bronchus respiratory epithelial cells Medium Supported Q99878 8331 +ENSG00000276368 HIST1H2AJ lung macrophages High Supported Q99878 8331 +ENSG00000276368 HIST1H2AJ lung pneumocytes High Supported Q99878 8331 +ENSG00000276410 HIST1H2BB bronchus respiratory epithelial cells High Supported P33778 3018 +ENSG00000276410 HIST1H2BB lung macrophages High Supported P33778 3018 +ENSG00000276410 HIST1H2BB lung pneumocytes High Supported P33778 3018 +ENSG00000276903 HIST1H2AL bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000276903 HIST1H2AL lung macrophages High Supported NA NA +ENSG00000276903 HIST1H2AL lung pneumocytes High Supported NA NA +ENSG00000276966 HIST1H4E bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000276966 HIST1H4E lung pneumocytes Low Supported NA NA +ENSG00000277075 HIST1H2AE bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000277075 HIST1H2AE lung macrophages Medium Supported NA NA +ENSG00000277075 HIST1H2AE lung pneumocytes High Supported NA NA +ENSG00000277157 HIST1H4D bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000277157 HIST1H4D lung pneumocytes Low Supported NA NA +ENSG00000277224 HIST1H2BF bronchus respiratory epithelial cells High Supported NA NA +ENSG00000277224 HIST1H2BF lung macrophages High Supported NA NA +ENSG00000277224 HIST1H2BF lung pneumocytes High Supported NA NA +ENSG00000277363 SRCIN1 bronchus respiratory epithelial cells Low Enhanced NA NA +ENSG00000277363 SRCIN1 lung macrophages Low Enhanced NA NA +ENSG00000277443 MARCKS bronchus respiratory epithelial cells High Enhanced P29966 4082 +ENSG00000277443 MARCKS lung pneumocytes Medium Enhanced P29966 4082 +ENSG00000277775 HIST1H3F bronchus respiratory epithelial cells High Supported NA NA +ENSG00000277775 HIST1H3F lung macrophages Medium Supported NA NA +ENSG00000277775 HIST1H3F lung pneumocytes High Supported NA NA +ENSG00000278272 HIST1H3C bronchus respiratory epithelial cells High Supported NA NA +ENSG00000278272 HIST1H3C lung macrophages Medium Supported NA NA +ENSG00000278272 HIST1H3C lung pneumocytes High Supported NA NA +ENSG00000278463 HIST1H2AB bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000278463 HIST1H2AB lung macrophages High Supported NA NA +ENSG00000278463 HIST1H2AB lung pneumocytes High Supported NA NA +ENSG00000278535 DHRS11 bronchus respiratory epithelial cells Low Enhanced NA NA +ENSG00000278588 HIST1H2BI bronchus respiratory epithelial cells High Supported NA NA +ENSG00000278588 HIST1H2BI lung macrophages High Supported NA NA +ENSG00000278588 HIST1H2BI lung pneumocytes High Supported NA NA +ENSG00000278619 MRM1 bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000278619 MRM1 lung macrophages Medium Supported NA NA +ENSG00000278637 HIST1H4A bronchus respiratory epithelial cells High Supported NA NA +ENSG00000278637 HIST1H4A lung macrophages High Supported NA NA +ENSG00000278637 HIST1H4A lung pneumocytes High Supported NA NA +ENSG00000278677 HIST1H2AM bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000278677 HIST1H2AM lung macrophages High Supported NA NA +ENSG00000278677 HIST1H2AM lung pneumocytes High Supported NA NA +ENSG00000278705 HIST1H4B bronchus respiratory epithelial cells Medium Supported NA NA +ENSG00000278705 HIST1H4B lung pneumocytes Low Supported NA NA +ENSG00000278828 HIST1H3H bronchus respiratory epithelial cells High Supported NA NA +ENSG00000278828 HIST1H3H lung macrophages Medium Supported NA NA +ENSG00000278828 HIST1H3H lung pneumocytes High Supported NA NA +ENSG00000278845 MRPL45 bronchus respiratory epithelial cells High Enhanced A0A087X2D5 84311 +ENSG00000278845 MRPL45 lung macrophages Medium Enhanced A0A087X2D5 84311 +ENSG00000278845 MRPL45 lung pneumocytes Low Enhanced A0A087X2D5 84311 +ENSG00000280987 MATR3 bronchus respiratory epithelial cells High Supported A8MXP9 NA +ENSG00000280987 MATR3 lung macrophages Medium Supported A8MXP9 NA +ENSG00000280987 MATR3 lung pneumocytes High Supported A8MXP9 NA +ENSG00000283496 ZNF511-PRAP1 bronchus respiratory epithelial cells Low Supported H7BY64 NA +ENSG00000283496 ZNF511-PRAP1 lung macrophages Low Supported H7BY64 NA
--- a/test-data/clusterProfiler_text_output.tabular Thu Mar 29 11:43:28 2018 -0400 +++ /dev/null Thu Jan 01 00:00:00 1970 +0000 @@ -1,378 +0,0 @@ -ID Description Count GeneRatio geneID -GO:0005886 plasma membrane 56 56/153 DSP/DSG1/ANXA2/JUP/MUC5B/ACTG1/FABP5/PIGR/ENO1/AZGP1/PLEC/TGM3/HRNR/ANXA1/HSPA5/TF/CAT/SERPINB12/CSTA/GAPDH/EEF2/MYH9/HSP90AA1/UBA52/FLNB/SOD1/HSPB1/HSPA8/EPPK1/GSTP1/DSC3/C1orf68/CTSV/CAPN1/VCL/YWHAE/IL1RN/SPRR1B/CST6/GSN/IDE/LYPD3/FLG/PERP/RPSA/LAMP1/LAMP2/RPS3/ATP5A1/PIP/MUC7/KRT1/KRT2/KRT10/SERPINA12/SPRR2E -GO:0005628 prospore membrane 0 0/153 -GO:0005789 endoplasmic reticulum membrane 1 1/153 HSPA5 -GO:0019867 outer membrane 2 2/153 ARG1/UBA52 -GO:0031090 organelle membrane 24 24/153 DSP/DSG1/ANXA2/FABP5/PIGR/LMNA/ANXA1/TF/CAT/SFN/SERPINB12/ARG1/GAPDH/SERPINA1/UBA52/DMBT1/HSPA8/YWHAZ/YWHAE/MDH2/LAMP1/LAMP2/RPS3/ATP5A1 -GO:0034357 photosynthetic membrane 0 0/153 -GO:0036362 ascus membrane 0 0/153 -GO:0042175 nuclear outer membrane-endoplasmic reticulum membrane network 1 1/153 HSPA5 -GO:0044425 membrane part 28 28/153 DSP/DSG1/ANXA2/JUP/PIGR/TGM3/ANXA1/HSPA5/TF/EEF2/MYH9/TUBA1B/HSP90AA1/CTSD/DMBT1/FLNB/HSPA8/EPPK1/DSC3/CTSV/PGK1/LYPD3/PERP/LAMP1/LAMP2/RPS3/ATP5A1/PIP -GO:0048475 coated membrane 0 0/153 -GO:0055036 virion membrane 0 0/153 -GO:0098552 side of membrane 8 8/153 DSG1/JUP/TGM3/ANXA1/TF/HSPA8/CTSV/LAMP1 -GO:0098589 membrane region 7 7/153 ANXA2/TF/EEF2/TUBA1B/CTSD/PGK1/LAMP2 -GO:0098590 plasma membrane region 10 10/153 DSP/DSG1/ANXA2/JUP/ANXA1/TF/HSP90AA1/EPPK1/RPS3/PIP -GO:0098796 membrane protein complex 3 3/153 JUP/MYH9/ATP5A1 -GO:0098805 whole membrane 19 19/153 DSP/DSG1/ANXA2/FABP5/PIGR/ANXA1/TF/CAT/SERPINB12/ARG1/EEF2/TUBA1B/CTSD/UBA52/DMBT1/HSPA8/PGK1/LAMP1/LAMP2 -GO:1990195 macrolide transmembrane transporter complex 0 0/153 -GO:1990196 MacAB-TolC complex 0 0/153 -GO:1990578 perinuclear endoplasmic reticulum membrane 0 0/153 -GO:1990850 H-gal-GP complex 0 0/153 -GO:0010367 extracellular isoamylase complex 0 0/153 -GO:0031012 extracellular matrix 28 28/153 DSP/DSG1/ANXA2/JUP/ACTG1/CASP14/PLEC/LMNA/HSPA5/PKM/PRDX1/CSTA/GAPDH/EEF2/MYH9/TUBB4B/SERPINA1/CTSD/FLNB/SOD1/HSPB1/HSPA8/EIF4A1/SBSN/RPS3/ATP5A1/KRT1/DCD -GO:0043083 synaptic cleft 0 0/153 -GO:0043230 extracellular organelle 130 130/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/AZGP1/PLEC/TGM3/KRT13/HRNR/KRT6B/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/LGALS7B/BLMH/FLNB/SOD1/HSPB1/HSPA8/EIF4A1/PPIA/YWHAZ/GGH/GSTP1/LCN1/SERPINB4/C1orf68/SBSN/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/HBB/A2ML1/HP/SERPINA3/ORM1/IL1RN/SPRR1B/SERPINB1/LCN2/CST6/S100A14/GSN/AGA/PSMA3/EEF1G/SERPINB5/MDH2/FCGBP/PNP/CSTB/ALDOC/KRT15/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP1/LAMP2/PPIB/RPS3/ATP5A1/CALML3/S100A11/CAPG/CAPZB/GSS/PSMB3/GDI2/ARPC4/ACTR2/NPC2/AMY1A/AMY1B/AMY1C/CALML5/PIP/ZG16B/CST4/MUC7/KRT1/KRT2/KRT10/FLG2/KPRP/DCD/DEFA3 -GO:0044421 extracellular region part 141 141/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/AZGP1/PLEC/TGM3/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/SERPINB7/LYZ/TUBA1B/SERPINA1/HSP90AA1/IL36G/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/CPA4/LGALS7B/BLMH/PLBD1/FLNB/SOD1/HSPB1/HSPA8/EIF4A1/PPIA/YWHAZ/GGH/GSTP1/LCN1/SERPINB4/C1orf68/SBSN/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/HBB/A2ML1/HP/SERPINA3/ORM1/IL1RN/SPRR1B/SERPINB1/LCN2/CST6/S100A14/GSN/IDE/AGA/PSMA3/EEF1G/SERPINB5/MDH2/FCGBP/LYPD3/PNP/CSTB/ALDOC/KRT15/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP1/LAMP2/PPIB/RPS3/ATP5A1/CALML3/S100A11/CAPG/CAPZB/GSS/PSMB3/GDI2/ARPC4/ACTR2/NPC2/AMY1A/AMY1B/AMY1C/CALML5/PIP/ZG16B/CST4/MUC7/CST1/CST2/KRT1/KRT2/KRT10/FLG2/KPRP/SERPINA12/DCD/DEFA3/KRT85 -GO:0048046 apoplast 0 0/153 -GO:0070062 extracellular exosome 130 130/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/AZGP1/PLEC/TGM3/KRT13/HRNR/KRT6B/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/LGALS7B/BLMH/FLNB/SOD1/HSPB1/HSPA8/EIF4A1/PPIA/YWHAZ/GGH/GSTP1/LCN1/SERPINB4/C1orf68/SBSN/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/HBB/A2ML1/HP/SERPINA3/ORM1/IL1RN/SPRR1B/SERPINB1/LCN2/CST6/S100A14/GSN/AGA/PSMA3/EEF1G/SERPINB5/MDH2/FCGBP/PNP/CSTB/ALDOC/KRT15/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP1/LAMP2/PPIB/RPS3/ATP5A1/CALML3/S100A11/CAPG/CAPZB/GSS/PSMB3/GDI2/ARPC4/ACTR2/NPC2/AMY1A/AMY1B/AMY1C/CALML5/PIP/ZG16B/CST4/MUC7/KRT1/KRT2/KRT10/FLG2/KPRP/DCD/DEFA3 -GO:0098595 perivitelline space 0 0/153 -GO:0099544 perisynaptic space 0 0/153 -GO:1903561 extracellular vesicle 130 130/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/AZGP1/PLEC/TGM3/KRT13/HRNR/KRT6B/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/LGALS7B/BLMH/FLNB/SOD1/HSPB1/HSPA8/EIF4A1/PPIA/YWHAZ/GGH/GSTP1/LCN1/SERPINB4/C1orf68/SBSN/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/HBB/A2ML1/HP/SERPINA3/ORM1/IL1RN/SPRR1B/SERPINB1/LCN2/CST6/S100A14/GSN/AGA/PSMA3/EEF1G/SERPINB5/MDH2/FCGBP/PNP/CSTB/ALDOC/KRT15/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP1/LAMP2/PPIB/RPS3/ATP5A1/CALML3/S100A11/CAPG/CAPZB/GSS/PSMB3/GDI2/ARPC4/ACTR2/NPC2/AMY1A/AMY1B/AMY1C/CALML5/PIP/ZG16B/CST4/MUC7/KRT1/KRT2/KRT10/FLG2/KPRP/DCD/DEFA3 -GO:0044464 cell part 136 136/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/AZGP1/PLEC/KRT80/TGM3/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/SERPINB7/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/LGALS7B/BLMH/PLBD1/FLNB/SOD1/HSPB1/HSPA8/EPPK1/EIF4A1/PPIA/YWHAZ/GGH/ALOX12B/GSTP1/SERPINB4/DSC3/C1orf68/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/HBB/KRT23/HP/SERPINA3/ORM1/IL1RN/SPRR1B/SERPINB1/LCN2/CST6/S100A14/GSN/IDE/AGA/PSMA3/EEF1G/SERPINB5/MDH2/LYPD3/PNP/CSTB/ALDOC/KRT15/FLG/PERP/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP1/LAMP2/TYMP/PPIB/RPS3/ATP5A1/S100A11/CAPG/HAL/CAPZB/GSS/PSMB3/GDI2/ARPC4/ACTR2/NPC2/CALML5/PIP/MUC7/KRT1/KRT2/KRT10/FLG2/KPRP/SERPINA12/SPRR2E/DEFA3/KRT85 -GO:1990065 Dxr protein complex 0 0/153 -GO:1990204 oxidoreductase complex 0 0/153 -GO:1990455 PTEN phosphatase complex 0 0/153 -GO:1990722 DAPK1-calmodulin complex 0 0/153 -GO:0039642 virion nucleoid 0 0/153 -GO:0042645 mitochondrial nucleoid 0 0/153 -GO:0042646 plastid nucleoid 0 0/153 -GO:0043590 bacterial nucleoid 0 0/153 -GO:0044777 single-stranded DNA-binding protein complex 0 0/153 -GO:0044423 virion part 0 0/153 -GO:0005911 cell-cell junction 13 13/153 DSP/DSG1/ANXA2/JUP/ANXA1/MYH9/POF1B/ACTN4/EPPK1/DSC3/VCL/PERP/S100A11 -GO:0030055 cell-substrate junction 25 25/153 JUP/ACTG1/PLEC/ANXA1/HSPA5/CAT/S100A7/HSPA1A/HSPA1B/MYH9/ACTN4/FLNB/HSPB1/HSPA8/EPPK1/PPIA/YWHAZ/CAPN1/VCL/YWHAE/GSN/PPIB/RPS3/GDI2/ACTR2 -GO:0061466 plasma membrane part of cell junction 0 0/153 -GO:0070161 anchoring junction 31 31/153 DSP/DSG1/ANXA2/JUP/ACTG1/PLEC/ANXA1/HSPA5/CAT/S100A7/HSPA1A/HSPA1B/MYH9/POF1B/ACTN4/FLNB/HSPB1/HSPA8/PPIA/YWHAZ/DSC3/CAPN1/VCL/YWHAE/GSN/PERP/PPIB/RPS3/S100A11/GDI2/ACTR2 -GO:0043233 organelle lumen 70 70/153 ALB/ANXA2/JUP/LTF/MUC5B/SERPINB3/FABP5/HRNR/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/PKM/ARG1/HSPA1A/HSPA1B/EEF2/TUBB4B/LYZ/SERPINA1/HSP90AA1/ACTN4/CTSD/UBA52/SOD1/HSPA8/EPPK1/PPIA/YWHAZ/GGH/GSTP1/CTSV/ALDOA/CAPN1/VCL/HBB/HP/SERPINA3/ORM1/SERPINB1/LCN2/S100A14/GSN/IDE/AGA/PSMA3/MDH2/PNP/CSTB/ALDOC/SERPINB13/CTSB/RPSA/LAMP2/PPIB/RPS3/ATP5A1/S100A11/CAPG/PSMB3/GDI2/ACTR2/NPC2/CALML5/MUC7/KRT1/FLG2/DEFA3 -GO:0001114 protein-DNA-RNA complex 0 0/153 -GO:0005952 cAMP-dependent protein kinase complex 0 0/153 -GO:0016533 cyclin-dependent protein kinase 5 holoenzyme complex 0 0/153 -GO:0017053 transcriptional repressor complex 0 0/153 -GO:0032992 protein-carbohydrate complex 0 0/153 -GO:0032993 protein-DNA complex 1 1/153 JUP -GO:0032994 protein-lipid complex 0 0/153 -GO:0034518 RNA cap binding complex 0 0/153 -GO:0035003 subapical complex 0 0/153 -GO:0036125 fatty acid beta-oxidation multienzyme complex 0 0/153 -GO:0043234 protein complex 30 30/153 ALB/ANXA2/JUP/LTF/ACTG1/ANXA1/HSPA5/GAPDH/MYH9/ACTN4/SOD1/HSPB1/HSPA8/EIF4A1/GSTP1/VCL/YWHAE/HBB/HP/GSN/IDE/PSMA3/PPIB/RPS3/ATP5A1/CAPG/CAPZB/PSMB3/ARPC4/ACTR2 -GO:0043235 receptor complex 3 3/153 PIGR/TF/MYH9 -GO:0044815 DNA packaging complex 0 0/153 -GO:0046536 dosage compensation complex 0 0/153 -GO:0061742 chaperone-mediated autophagy translocation complex 0 0/153 -GO:0061838 CENP-T-W-S-X complex 0 0/153 -GO:0070864 sperm individualization complex 0 0/153 -GO:0098636 protein complex involved in cell adhesion 1 1/153 MYH9 -GO:0098774 curli 0 0/153 -GO:0099023 tethering complex 0 0/153 -GO:0140007 KICSTOR complex 0 0/153 -GO:1902494 catalytic complex 8 8/153 ENO1/HSPA1A/HSPA1B/HSPB1/HSPA8/IDE/PSMA3/PSMB3 -GO:1902695 metallochaperone complex 0 0/153 -GO:1902773 GTPase activator complex 0 0/153 -GO:1903269 ornithine carbamoyltransferase inhibitor complex 0 0/153 -GO:1903502 translation repressor complex 0 0/153 -GO:1903503 ATPase inhibitor complex 0 0/153 -GO:1903865 sigma factor antagonist complex 0 0/153 -GO:1904090 peptidase inhibitor complex 0 0/153 -GO:1990104 DNA bending complex 0 0/153 -GO:1990229 iron-sulfur cluster assembly complex 0 0/153 -GO:1990249 nucleotide-excision repair, DNA damage recognition complex 0 0/153 -GO:1990351 transporter complex 0 0/153 -GO:1990391 DNA repair complex 0 0/153 -GO:1990415 Pex17p-Pex14p docking complex 0 0/153 -GO:1990684 protein-lipid-RNA complex 0 0/153 -GO:1990862 nuclear membrane complex Bqt3-Bqt4 0 0/153 -GO:1990904 ribonucleoprotein complex 10 10/153 GAPDH/HSPA1A/HSPA1B/EEF2/ACTN4/UBA52/HSPA8/APOD/RPSA/RPS3 -GO:1990923 PET complex 0 0/153 -GO:0000313 organellar ribosome 0 0/153 -GO:0005929 cilium 2 2/153 ANXA1/PKM -GO:0043227 membrane-bounded organelle 136 136/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/AZGP1/PLEC/TGM3/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/LGALS7B/BLMH/PLBD1/FLNB/SOD1/HSPB1/HSPA8/EPPK1/EIF4A1/PPIA/YWHAZ/GGH/GSTP1/LCN1/SERPINB4/C1orf68/SBSN/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/HBB/A2ML1/HP/SERPINA3/ORM1/IL1RN/SPRR1B/SERPINB1/LCN2/CST6/S100A14/GSN/IDE/AGA/PSMA3/EEF1G/SERPINB5/MDH2/FCGBP/PNP/CSTB/ALDOC/KRT15/FLG/PERP/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP1/LAMP2/PPIB/RPS3/ATP5A1/CALML3/S100A11/CAPG/CAPZB/GSS/PSMB3/GDI2/ARPC4/ACTR2/NPC2/AMY1A/AMY1B/AMY1C/CALML5/PIP/ZG16B/CST4/MUC7/KRT1/KRT2/KRT10/FLG2/KPRP/DCD/DEFA3 -GO:0043228 non-membrane-bounded organelle 51 51/153 DSP/KRT6A/KRT16/ANXA2/JUP/ACTG1/KRT78/KRT17/CASP14/ENO1/PLEC/KRT80/KRT13/KRT6B/LMNA/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/TUBA1B/ACTN4/UBA52/FLNB/HSPB1/HSPA8/EPPK1/CTSV/ALDOA/VCL/YWHAE/KRT23/GSN/PNP/CSTB/ALDOC/KRT15/FLG/APOD/CTSB/RPSA/RPS3/CAPG/CAPZB/ARPC4/ACTR2/KRT1/KRT2/KRT10/KRT85 -GO:0043229 intracellular organelle 115 115/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/AZGP1/PLEC/KRT80/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/LDHA/CTSD/UBA52/TXN/DMBT1/LGALS7B/BLMH/PLBD1/FLNB/SOD1/HSPB1/HSPA8/EPPK1/PPIA/YWHAZ/GGH/GSTP1/CTSV/ALDOA/CAPN1/VCL/YWHAE/HBB/KRT23/HP/SERPINA3/ORM1/SERPINB1/LCN2/S100A14/GSN/IDE/AGA/PSMA3/EEF1G/MDH2/PNP/CSTB/ALDOC/KRT15/FLG/PERP/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP1/LAMP2/PPIB/RPS3/ATP5A1/S100A11/CAPG/CAPZB/PSMB3/GDI2/ARPC4/ACTR2/NPC2/CALML5/PIP/MUC7/KRT1/KRT2/KRT10/FLG2/DEFA3/KRT85 -GO:0044422 organelle part 102 102/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/PLEC/KRT80/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/CTSD/UBA52/DMBT1/FLNB/SOD1/HSPB1/HSPA8/EPPK1/PPIA/YWHAZ/GGH/GSTP1/CTSV/ALDOA/CAPN1/VCL/YWHAE/HBB/KRT23/HP/SERPINA3/ORM1/SERPINB1/LCN2/S100A14/GSN/IDE/AGA/PSMA3/MDH2/PNP/CSTB/ALDOC/KRT15/FLG/SERPINB13/CTSB/RPSA/LAMP1/LAMP2/PPIB/RPS3/ATP5A1/S100A11/CAPG/CAPZB/PSMB3/GDI2/ARPC4/ACTR2/NPC2/CALML5/MUC7/KRT1/KRT2/KRT10/FLG2/DEFA3/KRT85 -GO:0097597 ventral disc 0 0/153 -GO:0099572 postsynaptic specialization 1 1/153 ACTR2 -GO:0018995 host 0 0/153 -GO:0044217 other organism part 0 0/153 -GO:0033643 host cell part 0 0/153 -GO:0043655 extracellular space of host 0 0/153 -GO:0044216 other organism cell 0 0/153 -GO:0044279 other organism membrane 0 0/153 -GO:0085036 extrahaustorial matrix 0 0/153 -GO:0085040 extra-invasive hyphal space 0 0/153 -GO:0005577 fibrinogen complex 0 0/153 -GO:0005601 classical-complement-pathway C3/C5 convertase complex 0 0/153 -GO:0005602 complement component C1 complex 0 0/153 -GO:0005615 extracellular space 78 78/153 ALB/ANXA2/LTF/MUC5B/SERPINB3/ACTG1/KRT78/PIGR/ENO1/AZGP1/ANXA1/TF/CAT/SFN/SERPINB12/TPI1/PRDX1/CSTA/ARG1/HSPA1A/HSPA1B/SERPINB7/LYZ/SERPINA1/IL36G/ACTN4/CTSD/UBA52/DMBT1/CPA4/LGALS7B/PLBD1/SOD1/HSPB1/HSPA8/PPIA/YWHAZ/GGH/GSTP1/LCN1/SERPINB4/CTSV/PGK1/ALDOA/HBB/A2ML1/HP/SERPINA3/ORM1/IL1RN/SERPINB1/LCN2/GSN/IDE/AGA/SERPINB5/LYPD3/CSTB/SERPINB13/APOD/CTSB/LAMP2/S100A11/NPC2/AMY1A/AMY1B/AMY1C/PIP/ZG16B/CST4/CST1/CST2/KRT1/KRT2/KRT10/SERPINA12/DEFA3/KRT85 -GO:0005616 larval serum protein complex 0 0/153 -GO:0016942 insulin-like growth factor binding protein complex 0 0/153 -GO:0020004 symbiont-containing vacuolar space 0 0/153 -GO:0020005 symbiont-containing vacuole membrane 0 0/153 -GO:0020006 symbiont-containing vacuolar membrane network 0 0/153 -GO:0031395 bursicon neuropeptide hormone complex 0 0/153 -GO:0032311 angiogenin-PRI complex 0 0/153 -GO:0034358 plasma lipoprotein particle 0 0/153 -GO:0035182 female germline ring canal outer rim 0 0/153 -GO:0035183 female germline ring canal inner rim 0 0/153 -GO:0036117 hyaluranon cable 0 0/153 -GO:0042571 immunoglobulin complex, circulating 0 0/153 -GO:0043245 extraorganismal space 0 0/153 -GO:0043511 inhibin complex 0 0/153 -GO:0043514 interleukin-12 complex 0 0/153 -GO:0044420 extracellular matrix component 1 1/153 ANXA2 -GO:0045171 intercellular bridge 0 0/153 -GO:0048180 activin complex 0 0/153 -GO:0061696 pituitary gonadotropin complex 0 0/153 -GO:0070289 extracellular ferritin complex 0 0/153 -GO:0070701 mucus layer 1 1/153 MUC5B -GO:0070743 interleukin-23 complex 0 0/153 -GO:0070744 interleukin-27 complex 0 0/153 -GO:0070745 interleukin-35 complex 0 0/153 -GO:0072562 blood microparticle 13 13/153 ALB/ACTG1/TF/HSPA1A/HSPA1B/HSPA8/YWHAZ/HBB/HP/SERPINA3/ORM1/GSN/KRT1 -GO:0097058 CRLF-CLCF1 complex 0 0/153 -GO:0097059 CNTFR-CLCF1 complex 0 0/153 -GO:0097619 PTEX complex 0 0/153 -GO:1990296 scaffoldin complex 0 0/153 -GO:1990563 extracellular exosome complex 0 0/153 -GO:1990903 extracellular ribonucleoprotein complex 0 0/153 -GO:0030094 plasma membrane-derived photosystem I 0 0/153 -GO:0030096 plasma membrane-derived thylakoid photosystem II 0 0/153 -GO:0031300 intrinsic component of organelle membrane 1 1/153 LAMP2 -GO:0031676 plasma membrane-derived thylakoid membrane 0 0/153 -GO:0032420 stereocilium 0 0/153 -GO:0032426 stereocilium tip 0 0/153 -GO:0044232 organelle membrane contact site 0 0/153 -GO:0044441 ciliary part 0 0/153 -GO:0044446 intracellular organelle part 100 100/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/KRT80/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/CTSD/UBA52/DMBT1/FLNB/SOD1/HSPB1/HSPA8/EPPK1/PPIA/YWHAZ/GGH/GSTP1/CTSV/ALDOA/CAPN1/VCL/YWHAE/HBB/KRT23/HP/SERPINA3/ORM1/SERPINB1/LCN2/S100A14/GSN/IDE/AGA/PSMA3/MDH2/PNP/CSTB/ALDOC/KRT15/FLG/SERPINB13/CTSB/RPSA/LAMP1/LAMP2/PPIB/RPS3/ATP5A1/S100A11/CAPG/CAPZB/PSMB3/GDI2/ARPC4/ACTR2/NPC2/CALML5/MUC7/KRT1/KRT2/KRT10/FLG2/DEFA3/KRT85 -GO:0044449 contractile fiber part 9 9/153 JUP/ENO1/PLEC/ACTN4/FLNB/HSPB1/ALDOA/VCL/CAPZB -GO:0044461 bacterial-type flagellum part 0 0/153 -GO:0044695 Dsc E3 ubiquitin ligase complex 0 0/153 -GO:0048493 plasma membrane-derived thylakoid ribulose bisphosphate carboxylase complex 0 0/153 -GO:0060091 kinocilium 0 0/153 -GO:0060171 stereocilium membrane 0 0/153 -GO:0097591 ventral disc lateral crest 0 0/153 -GO:0097592 ventral disc overlap zone 0 0/153 -GO:0097593 ventral disc microtubule array 0 0/153 -GO:0097594 ventral disc dorsal microribbon 0 0/153 -GO:0097595 ventral disc crossbridge 0 0/153 -GO:0097596 ventral disc supernumerary microtubule array 0 0/153 -GO:0098576 lumenal side of membrane 1 1/153 HSPA8 -GO:0098892 extrinsic component of postsynaptic specialization membrane 0 0/153 -GO:0098948 intrinsic component of postsynaptic specialization membrane 0 0/153 -GO:0099091 postsynaptic specialization, intracellular component 0 0/153 -GO:0099092 postsynaptic density, intracellular component 0 0/153 -GO:0099634 postsynaptic specialization membrane 0 0/153 -GO:1990070 TRAPPI protein complex 0 0/153 -GO:1990121 H-NS complex 0 0/153 -GO:1990177 IHF-DNA complex 0 0/153 -GO:1990178 HU-DNA complex 0 0/153 -GO:1990500 eif4e-cup complex 0 0/153 -GO:0019013 viral nucleocapsid 0 0/153 -GO:0019015 viral genome 0 0/153 -GO:0019028 viral capsid 0 0/153 -GO:0019033 viral tegument 0 0/153 -GO:0036338 viral membrane 0 0/153 -GO:0039624 viral outer capsid 0 0/153 -GO:0039625 viral inner capsid 0 0/153 -GO:0039626 viral intermediate capsid 0 0/153 -GO:0046727 capsomere 0 0/153 -GO:0046729 viral procapsid 0 0/153 -GO:0046798 viral portal complex 0 0/153 -GO:0046806 viral scaffold 0 0/153 -GO:0098015 virus tail 0 0/153 -GO:0098019 virus tail, major subunit 0 0/153 -GO:0098020 virus tail, minor subunit 0 0/153 -GO:0098021 viral capsid, decoration 0 0/153 -GO:0098023 virus tail, tip 0 0/153 -GO:0098024 virus tail, fiber 0 0/153 -GO:0098025 virus tail, baseplate 0 0/153 -GO:0098026 virus tail, tube 0 0/153 -GO:0098027 virus tail, sheath 0 0/153 -GO:0098028 virus tail, shaft 0 0/153 -GO:0098029 icosahedral viral capsid, spike 0 0/153 -GO:0098030 icosahedral viral capsid, neck 0 0/153 -GO:0098031 icosahedral viral capsid, collar 0 0/153 -GO:0098061 viral capsid, internal space 0 0/153 -GO:0000136 alpha-1,6-mannosyltransferase complex 0 0/153 -GO:0019898 extrinsic component of membrane 6 6/153 ANXA2/JUP/TGM3/ANXA1/TF/DMBT1 -GO:0000835 ER ubiquitin ligase complex 0 0/153 -GO:0005640 nuclear outer membrane 0 0/153 -GO:0005942 phosphatidylinositol 3-kinase complex 0 0/153 -GO:0008250 oligosaccharyltransferase complex 0 0/153 -GO:0009654 photosystem II oxygen evolving complex 0 0/153 -GO:0009923 fatty acid elongase complex 0 0/153 -GO:0030964 NADH dehydrogenase complex 0 0/153 -GO:0031211 endoplasmic reticulum palmitoyltransferase complex 0 0/153 -GO:0031224 intrinsic component of membrane 10 10/153 DSG1/PIGR/HSPA5/MYH9/FLNB/DSC3/LYPD3/PERP/LAMP1/LAMP2 -GO:0031502 dolichyl-phosphate-mannose-protein mannosyltransferase complex 0 0/153 -GO:0042765 GPI-anchor transamidase complex 0 0/153 -GO:0044453 nuclear membrane part 0 0/153 -GO:0044455 mitochondrial membrane part 1 1/153 ATP5A1 -GO:0044459 plasma membrane part 17 17/153 DSP/DSG1/ANXA2/JUP/PIGR/TGM3/ANXA1/TF/MYH9/HSP90AA1/EPPK1/CTSV/LYPD3/PERP/LAMP1/RPS3/PIP -GO:0045281 succinate dehydrogenase complex 0 0/153 -GO:0046696 lipopolysaccharide receptor complex 0 0/153 -GO:0070057 prospore membrane spindle pole body attachment site 0 0/153 -GO:0070469 respiratory chain 0 0/153 -GO:0071595 Nem1-Spo7 phosphatase complex 0 0/153 -GO:0097478 leaflet of membrane bilayer 0 0/153 -GO:1902495 transmembrane transporter complex 0 0/153 -GO:1990332 Ire1 complex 0 0/153 -GO:0008021 synaptic vesicle 1 1/153 LAMP1 -GO:0030129 clathrin coat of synaptic vesicle 0 0/153 -GO:0030672 synaptic vesicle membrane 0 0/153 -GO:0034592 synaptic vesicle lumen 0 0/153 -GO:0044326 dendritic spine neck 0 0/153 -GO:0044327 dendritic spine head 0 0/153 -GO:0048786 presynaptic active zone 0 0/153 -GO:0061846 dendritic spine cytoplasm 0 0/153 -GO:0071212 subsynaptic reticulum 0 0/153 -GO:0097060 synaptic membrane 0 0/153 -GO:0097444 spine apparatus 0 0/153 -GO:0097445 presynaptic active zone dense projection 0 0/153 -GO:0098563 intrinsic component of synaptic vesicle membrane 0 0/153 -GO:0098682 arciform density 0 0/153 -GO:0098793 presynapse 2 2/153 HSPA8/LAMP1 -GO:0098794 postsynapse 1 1/153 ACTR2 -GO:0098830 presynaptic endosome 0 0/153 -GO:0098831 presynaptic active zone cytoplasmic component 0 0/153 -GO:0098833 presynaptic endocytic zone 0 0/153 -GO:0098834 presynaptic endocytic zone cytoplasmic component 0 0/153 -GO:0098843 postsynaptic endocytic zone 0 0/153 -GO:0098845 postsynaptic endosome 0 0/153 -GO:0098850 extrinsic component of synaptic vesicle membrane 0 0/153 -GO:0098888 extrinsic component of presynaptic membrane 0 0/153 -GO:0098889 intrinsic component of presynaptic membrane 0 0/153 -GO:0098890 extrinsic component of postsynaptic membrane 0 0/153 -GO:0098895 postsynaptic endosome membrane 0 0/153 -GO:0098897 spine apparatus membrane 0 0/153 -GO:0098899 spine apparatus lumen 0 0/153 -GO:0098929 extrinsic component of spine apparatus membrane 0 0/153 -GO:0098936 intrinsic component of postsynaptic membrane 0 0/153 -GO:0098949 intrinsic component of postsynaptic endosome membrane 0 0/153 -GO:0098952 intrinsic component of spine apparatus membrane 0 0/153 -GO:0098954 presynaptic endosome membrane 0 0/153 -GO:0098955 intrinsic component of presynaptic endosome membrane 0 0/153 -GO:0098965 extracellular matrix of synaptic cleft 0 0/153 -GO:0098999 extrinsic component of postsynaptic endosome membrane 0 0/153 -GO:0099007 extrinsic component of presynaptic endosome membrane 0 0/153 -GO:0099523 presynaptic cytosol 0 0/153 -GO:0099524 postsynaptic cytosol 0 0/153 -GO:0099569 presynaptic cytoskeleton 0 0/153 -GO:0099571 postsynaptic cytoskeleton 0 0/153 -GO:0099631 postsynaptic endocytic zone cytoplasmic component 0 0/153 -GO:1990013 presynaptic grid 0 0/153 -GO:1990780 cytoplasmic side of dendritic spine plasma membrane 0 0/153 -GO:0005622 intracellular 133 133/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/AZGP1/PLEC/KRT80/TGM3/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/SERPINB7/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/LGALS7B/BLMH/PLBD1/FLNB/SOD1/HSPB1/HSPA8/EPPK1/EIF4A1/PPIA/YWHAZ/GGH/ALOX12B/GSTP1/SERPINB4/DSC3/C1orf68/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/HBB/KRT23/HP/SERPINA3/ORM1/IL1RN/SPRR1B/SERPINB1/LCN2/S100A14/GSN/IDE/AGA/PSMA3/EEF1G/SERPINB5/MDH2/PNP/CSTB/ALDOC/KRT15/FLG/PERP/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP1/LAMP2/TYMP/PPIB/RPS3/ATP5A1/S100A11/CAPG/HAL/CAPZB/GSS/PSMB3/GDI2/ARPC4/ACTR2/NPC2/CALML5/PIP/MUC7/KRT1/KRT2/KRT10/FLG2/KPRP/SPRR2E/DEFA3/KRT85 -GO:0005642 annulate lamellae 0 0/153 -GO:0005905 clathrin-coated pit 1 1/153 TF -GO:0005933 cellular bud 0 0/153 -GO:0005966 cyclic-nucleotide phosphodiesterase complex 0 0/153 -GO:0008287 protein serine/threonine phosphatase complex 0 0/153 -GO:0009344 nitrite reductase complex [NAD(P)H] 0 0/153 -GO:0009347 aspartate carbamoyltransferase complex 0 0/153 -GO:0009349 riboflavin synthase complex 0 0/153 -GO:0009358 polyphosphate kinase complex 0 0/153 -GO:0009930 longitudinal side of cell surface 0 0/153 -GO:0009986 cell surface 10 10/153 ANXA2/LTF/ENO1/ANXA1/HSPA5/TF/MYH9/CTSV/IDE/LAMP1 -GO:0012505 endomembrane system 69 69/153 DSP/ALB/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/FABP5/PIGR/HRNR/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SERPINB12/PKM/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/TUBB4B/LYZ/SERPINA1/HSP90AA1/ACTN4/CTSD/UBA52/DMBT1/SOD1/HSPA8/PPIA/GGH/GSTP1/CTSV/ALDOA/CAPN1/VCL/HBB/HP/SERPINA3/ORM1/SERPINB1/LCN2/GSN/AGA/EEF1G/PNP/CSTB/ALDOC/PERP/APOD/CTSB/LAMP1/LAMP2/PPIB/RPS3/S100A11/GDI2/ACTR2/NPC2/CALML5/MUC7/KRT1/FLG2/DEFA3 -GO:0015627 type II protein secretion system complex 0 0/153 -GO:0019008 molybdopterin synthase complex 0 0/153 -GO:0020007 apical complex 0 0/153 -GO:0020008 rhoptry 0 0/153 -GO:0020031 polar ring of apical complex 0 0/153 -GO:0020032 basal ring of apical complex 0 0/153 -GO:0020039 pellicle 0 0/153 -GO:0030256 type I protein secretion system complex 0 0/153 -GO:0030257 type III protein secretion system complex 0 0/153 -GO:0030312 external encapsulating structure 0 0/153 -GO:0030427 site of polarized growth 1 1/153 YWHAE -GO:0030428 cell septum 0 0/153 -GO:0030496 midbody 3 3/153 ANXA2/HSPA5/CAPG -GO:0030904 retromer complex 0 0/153 -GO:0030905 retromer, tubulation complex 0 0/153 -GO:0030906 retromer, cargo-selective complex 0 0/153 -GO:0031252 cell leading edge 7 7/153 ANXA2/MYH9/HSP90AA1/GSN/RPS3/S100A11/ACTR2 -GO:0031254 cell trailing edge 1 1/153 MYH9 -GO:0031317 tripartite ATP-independent periplasmic transporter complex 0 0/153 -GO:0031521 spitzenkorper 0 0/153 -GO:0031522 cell envelope Sec protein transport complex 0 0/153 -GO:0031975 envelope 10 10/153 LMNA/ANXA1/CAT/ARG1/GAPDH/UBA52/SOD1/MDH2/RPS3/ATP5A1 -GO:0032126 eisosome 0 0/153 -GO:0032153 cell division site 1 1/153 MYH9 -GO:0032155 cell division site part 1 1/153 MYH9 -GO:0032179 germ tube 0 0/153 -GO:0032766 NHE3/E3KARP/ACTN4 complex 0 0/153 -GO:0033016 rhoptry membrane 0 0/153 -GO:0033104 type VI protein secretion system complex 0 0/153 -GO:0033774 basal labyrinth 0 0/153 -GO:0034591 rhoptry lumen 0 0/153 -GO:0035748 myelin sheath abaxonal region 0 0/153 -GO:0035749 myelin sheath adaxonal region 1 1/153 ANXA2 -GO:0036375 Kibra-Ex-Mer complex 0 0/153 -GO:0042597 periplasmic space 0 0/153 -GO:0042763 intracellular immature spore 0 0/153 -GO:0042995 cell projection 20 20/153 ANXA2/ANXA1/PKM/ARG1/MYH9/HSP90AA1/ACTN4/FLNB/SOD1/HSPB1/EPPK1/CTSV/YWHAE/GSN/APOD/LAMP1/RPS3/S100A11/ARPC4/ACTR2 -GO:0043209 myelin sheath 15 15/153 ALB/ANXA2/ACTG1/HSPA5/PKM/PRDX1/TUBB4B/TUBA1B/HSP90AA1/SOD1/HSPA8/GSN/MDH2/ATP5A1/GDI2 -GO:0043218 compact myelin 1 1/153 ANXA2 -GO:0043219 lateral loop 0 0/153 -GO:0043220 Schmidt-Lanterman incisure 1 1/153 ANXA2 -GO:0043684 type IV secretion system complex 0 0/153 -GO:0044099 polar tube 0 0/153 -GO:0044297 cell body 6 6/153 ARG1/FLNB/SOD1/CTSV/APOD/LAMP1 -GO:0044424 intracellular part 133 133/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/AZGP1/PLEC/KRT80/TGM3/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/SERPINB7/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/LGALS7B/BLMH/PLBD1/FLNB/SOD1/HSPB1/HSPA8/EPPK1/EIF4A1/PPIA/YWHAZ/GGH/ALOX12B/GSTP1/SERPINB4/DSC3/C1orf68/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/HBB/KRT23/HP/SERPINA3/ORM1/IL1RN/SPRR1B/SERPINB1/LCN2/S100A14/GSN/IDE/AGA/PSMA3/EEF1G/SERPINB5/MDH2/PNP/CSTB/ALDOC/KRT15/FLG/PERP/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP1/LAMP2/TYMP/PPIB/RPS3/ATP5A1/S100A11/CAPG/HAL/CAPZB/GSS/PSMB3/GDI2/ARPC4/ACTR2/NPC2/CALML5/PIP/MUC7/KRT1/KRT2/KRT10/FLG2/KPRP/SPRR2E/DEFA3/KRT85 -GO:0044457 cell septum part 0 0/153 -GO:0044462 external encapsulating structure part 0 0/153 -GO:0044463 cell projection part 5 5/153 HSP90AA1/SOD1/HSPB1/YWHAE/RPS3 -GO:0044697 HICS complex 0 0/153 -GO:0045177 apical part of cell 5 5/153 DSG1/ANXA1/TF/CTSV/PIP -GO:0045178 basal part of cell 1 1/153 TF -GO:0051286 cell tip 0 0/153 -GO:0060187 cell pole 0 0/153 -GO:0061835 ventral surface of cell 0 0/153 -GO:0070056 prospore membrane leading edge 0 0/153 -GO:0070258 inner membrane complex 0 0/153 -GO:0070331 CD20-Lck-Fyn complex 0 0/153 -GO:0070332 CD20-Lck-Lyn-Fyn complex 0 0/153 -GO:0070938 contractile ring 1 1/153 MYH9 -GO:0071944 cell periphery 59 59/153 DSP/DSG1/ANXA2/JUP/MUC5B/ACTG1/KRT17/FABP5/PIGR/ENO1/AZGP1/PLEC/TGM3/HRNR/ANXA1/HSPA5/TF/CAT/SERPINB12/CSTA/GAPDH/EEF2/MYH9/HSP90AA1/ACTN4/UBA52/FLNB/SOD1/HSPB1/HSPA8/EPPK1/GSTP1/DSC3/C1orf68/CTSV/CAPN1/VCL/YWHAE/IL1RN/SPRR1B/CST6/GSN/IDE/LYPD3/FLG/PERP/RPSA/LAMP1/LAMP2/RPS3/ATP5A1/ACTR2/PIP/MUC7/KRT1/KRT2/KRT10/SERPINA12/SPRR2E -GO:0072324 ascus epiplasm 0 0/153 -GO:0090543 Flemming body 1 1/153 CAPG -GO:0090635 extracellular core region of desmosome 0 0/153 -GO:0090636 outer dense plaque of desmosome 0 0/153 -GO:0090637 inner dense plaque of desmosome 0 0/153 -GO:0097223 sperm part 0 0/153 -GO:0097268 cytoophidium 0 0/153 -GO:0097458 neuron part 10 10/153 ARG1/ACTN4/FLNB/SOD1/HSPB1/HSPA8/CTSV/YWHAE/APOD/LAMP1 -GO:0097569 lateral shield 0 0/153 -GO:0097574 lateral part of cell 0 0/153 -GO:0097610 cell surface furrow 1 1/153 MYH9 -GO:0097613 dinoflagellate epicone 0 0/153 -GO:0097614 dinoflagellate hypocone 0 0/153 -GO:0097653 unencapsulated part of cell 0 0/153 -GO:0097683 dinoflagellate apex 0 0/153 -GO:0097684 dinoflagellate antapex 0 0/153 -GO:0098046 type V protein secretion system complex 0 0/153 -GO:0098862 cluster of actin-based cell projections 4 4/153 PLEC/MYH9/ACTN4/FLNB -GO:1990015 ensheathing process 0 0/153 -GO:1990016 neck portion of tanycyte 0 0/153 -GO:1990018 tail portion of tanycyte 0 0/153 -GO:1990225 rhoptry neck 0 0/153 -GO:1990794 basolateral part of cell 0 0/153 -GO:0031594 neuromuscular junction 1 1/153 MYH9 -GO:0044456 synapse part 3 3/153 HSPA8/LAMP1/ACTR2 -GO:0060076 excitatory synapse 0 0/153 -GO:0060077 inhibitory synapse 0 0/153 -GO:0097470 ribbon synapse 0 0/153 -GO:0098685 Schaffer collateral - CA1 synapse 0 0/153 -GO:0098686 hippocampal mossy fiber to CA3 synapse 0 0/153 -GO:0098978 glutamatergic synapse 0 0/153 -GO:0098979 polyadic synapse 0 0/153 -GO:0098981 cholinergic synapse 0 0/153 -GO:0098982 GABA-ergic synapse 0 0/153 -GO:0098984 neuron to neuron synapse 1 1/153 ACTR2 -GO:0009506 plasmodesma 0 0/153 -GO:0005818 aster 0 0/153 -GO:0097740 paraflagellar rod 0 0/153 -GO:0097741 mastigoneme 0 0/153 -GO:0098644 complex of collagen trimers 0 0/153 -GO:0099081 supramolecular polymer 30 30/153 DSP/KRT6A/KRT16/JUP/ACTG1/KRT78/KRT17/CASP14/ENO1/PLEC/KRT80/KRT13/KRT6B/LMNA/TUBB4B/TUBA1B/ACTN4/FLNB/HSPB1/EPPK1/ALDOA/VCL/KRT23/KRT15/FLG/CAPZB/KRT1/KRT2/KRT10/KRT85
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/cluster_profiler_EGO_BP.csv Tue Dec 18 09:21:32 2018 -0500 @@ -0,0 +1,20 @@ +ID Description GeneRatio BgRatio pvalue p.adjust qvalue geneID Count +GO:0002283 neutrophil activation involved in immune response 27/149 168/2853 5.99262610186788e-08 5.02726307819038e-05 5.02726307819038e-05 DSP/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/CAT/EEF2/TUBB4B/LYZ/CTSD/GSTP1/ALDOA/CAPN1/VCL/SERPINA3/LCN2/GSN/AGA/PNP/LAMP1/LAMP2/S100A11/GDI2/NPC2 27 +GO:0043312 neutrophil degranulation 27/149 168/2853 5.99262610186788e-08 5.02726307819038e-05 5.02726307819038e-05 DSP/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/CAT/EEF2/TUBB4B/LYZ/CTSD/GSTP1/ALDOA/CAPN1/VCL/SERPINA3/LCN2/GSN/AGA/PNP/LAMP1/LAMP2/S100A11/GDI2/NPC2 27 +GO:0002446 neutrophil mediated immunity 27/149 169/2853 6.82352392138906e-08 5.02726307819038e-05 5.02726307819038e-05 DSP/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/CAT/EEF2/TUBB4B/LYZ/CTSD/GSTP1/ALDOA/CAPN1/VCL/SERPINA3/LCN2/GSN/AGA/PNP/LAMP1/LAMP2/S100A11/GDI2/NPC2 27 +GO:0042119 neutrophil activation 27/149 172/2853 1.00061112604686e-07 5.02726307819038e-05 5.02726307819038e-05 DSP/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/CAT/EEF2/TUBB4B/LYZ/CTSD/GSTP1/ALDOA/CAPN1/VCL/SERPINA3/LCN2/GSN/AGA/PNP/LAMP1/LAMP2/S100A11/GDI2/NPC2 27 +GO:0036230 granulocyte activation 27/149 173/2853 1.13431026132454e-07 5.02726307819038e-05 5.02726307819038e-05 DSP/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/CAT/EEF2/TUBB4B/LYZ/CTSD/GSTP1/ALDOA/CAPN1/VCL/SERPINA3/LCN2/GSN/AGA/PNP/LAMP1/LAMP2/S100A11/GDI2/NPC2 27 +GO:0043299 leukocyte degranulation 27/149 180/2853 2.65006585212016e-07 8.25330901595836e-05 8.25330901595836e-05 DSP/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/CAT/EEF2/TUBB4B/LYZ/CTSD/GSTP1/ALDOA/CAPN1/VCL/SERPINA3/LCN2/GSN/AGA/PNP/LAMP1/LAMP2/S100A11/GDI2/NPC2 27 +GO:0031424 keratinization 10/149 26/2853 2.89179325599142e-07 8.25330901595836e-05 8.25330901595836e-05 DSP/KRT6A/DSG1/JUP/KRT17/KRT6B/SFN/CSTA/CAPN1/KRT15 10 +GO:0002444 myeloid leukocyte mediated immunity 27/149 181/2853 2.97953394077919e-07 8.25330901595836e-05 8.25330901595836e-05 DSP/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/CAT/EEF2/TUBB4B/LYZ/CTSD/GSTP1/ALDOA/CAPN1/VCL/SERPINA3/LCN2/GSN/AGA/PNP/LAMP1/LAMP2/S100A11/GDI2/NPC2 27 +GO:0002275 myeloid cell activation involved in immune response 27/149 183/2853 3.75549726596481e-07 9.24686882375336e-05 9.24686882375336e-05 DSP/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/CAT/EEF2/TUBB4B/LYZ/CTSD/GSTP1/ALDOA/CAPN1/VCL/SERPINA3/LCN2/GSN/AGA/PNP/LAMP1/LAMP2/S100A11/GDI2/NPC2 27 +GO:0070268 cornification 9/149 23/2853 9.92125868947906e-07 0.000219855092558856 0.000219855092558856 DSP/KRT6A/DSG1/JUP/KRT17/KRT6B/CSTA/CAPN1/KRT15 9 +GO:0045055 regulated exocytosis 29/149 223/2853 2.0213368484075e-06 0.000407207496006457 0.000407207496006457 DSP/ALB/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/CAT/EEF2/TUBB4B/LYZ/CTSD/SOD1/GSTP1/ALDOA/CAPN1/VCL/SERPINA3/LCN2/GSN/AGA/PNP/LAMP1/LAMP2/S100A11/GDI2/NPC2 29 +GO:0002274 myeloid leukocyte activation 27/149 203/2853 3.12478790836653e-06 0.000577044167078353 0.000577044167078353 DSP/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/CAT/EEF2/TUBB4B/LYZ/CTSD/GSTP1/ALDOA/CAPN1/VCL/SERPINA3/LCN2/GSN/AGA/PNP/LAMP1/LAMP2/S100A11/GDI2/NPC2 27 +GO:0006887 exocytosis 30/149 244/2853 4.33119966176751e-06 0.000738302957728985 0.000738302957728985 DSP/ALB/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/ANXA1/CAT/EEF2/TUBB4B/LYZ/CTSD/SOD1/GSTP1/ALDOA/CAPN1/VCL/SERPINA3/LCN2/GSN/AGA/PNP/LAMP1/LAMP2/S100A11/GDI2/NPC2 30 +GO:0002366 leukocyte activation involved in immune response 28/149 221/2853 5.31851626919331e-06 0.000806185471823388 0.000806185471823388 DSP/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/ANXA1/CAT/EEF2/TUBB4B/LYZ/CTSD/GSTP1/ALDOA/CAPN1/VCL/SERPINA3/LCN2/GSN/AGA/PNP/LAMP1/LAMP2/S100A11/GDI2/NPC2 28 +GO:0030216 keratinocyte differentiation 12/149 50/2853 5.7487351124723e-06 0.000806185471823388 0.000806185471823388 DSP/KRT6A/DSG1/JUP/KRT17/KRT6B/ANXA1/SFN/CSTA/FLNB/CAPN1/KRT15 12 +GO:0002263 cell activation involved in immune response 28/149 222/2853 5.82083373157681e-06 0.000806185471823388 0.000806185471823388 DSP/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/ANXA1/CAT/EEF2/TUBB4B/LYZ/CTSD/GSTP1/ALDOA/CAPN1/VCL/SERPINA3/LCN2/GSN/AGA/PNP/LAMP1/LAMP2/S100A11/GDI2/NPC2 28 +GO:0009913 epidermal cell differentiation 13/149 60/2853 7.8304899549941e-06 0.00102072739648629 0.00102072739648629 DSP/KRT6A/DSG1/JUP/KRT17/KRT6B/ANXA1/SFN/CSTA/FLNB/SOD1/CAPN1/KRT15 13 +GO:0002443 leukocyte mediated immunity 28/149 241/2853 2.87263795698714e-05 0.00353653650704639 0.00353653650704639 DSP/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/CAT/EEF2/TUBB4B/LYZ/CTSD/GSTP1/SERPINB4/ALDOA/CAPN1/VCL/SERPINA3/LCN2/GSN/AGA/PNP/LAMP1/LAMP2/S100A11/GDI2/NPC2 28 +GO:0008544 epidermis development 14/149 83/2853 7.05318311161389e-05 0.00822623882912441 0.00822623882912441 DSP/KRT6A/DSG1/JUP/KRT17/FABP5/KRT6B/ANXA1/SFN/CSTA/FLNB/SOD1/CAPN1/KRT15 14
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/cluster_profiler_EGO_CC.csv Tue Dec 18 09:21:32 2018 -0500 @@ -0,0 +1,18 @@ +ID Description GeneRatio BgRatio pvalue p.adjust qvalue geneID Count +GO:0034774 secretory granule lumen 22/152 111/2939 2.07482731603193e-08 3.16370874431657e-06 2.781282412586e-06 ALB/ANXA2/JUP/LTF/SERPINB3/FABP5/CAT/EEF2/TUBB4B/LYZ/CTSD/GSTP1/ALDOA/VCL/SERPINA3/LCN2/GSN/AGA/PNP/S100A11/GDI2/NPC2 22 +GO:0031983 vesicle lumen 22/152 114/2939 3.4766030157325e-08 3.16370874431657e-06 2.781282412586e-06 ALB/ANXA2/JUP/LTF/SERPINB3/FABP5/CAT/EEF2/TUBB4B/LYZ/CTSD/GSTP1/ALDOA/VCL/SERPINA3/LCN2/GSN/AGA/PNP/S100A11/GDI2/NPC2 22 +GO:0060205 cytoplasmic vesicle lumen 22/152 114/2939 3.4766030157325e-08 3.16370874431657e-06 2.781282412586e-06 ALB/ANXA2/JUP/LTF/SERPINB3/FABP5/CAT/EEF2/TUBB4B/LYZ/CTSD/GSTP1/ALDOA/VCL/SERPINA3/LCN2/GSN/AGA/PNP/S100A11/GDI2/NPC2 22 +GO:0030141 secretory granule 30/152 232/2939 1.22925605779538e-06 8.38967259445349e-05 7.3755363467723e-05 DSP/ALB/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/CAT/EEF2/TUBB4B/LYZ/CTSD/DMBT1/SOD1/GSTP1/ALDOA/CAPN1/VCL/SERPINA3/LCN2/GSN/AGA/PNP/LAMP1/LAMP2/S100A11/GDI2/NPC2 30 +GO:0099503 secretory vesicle 30/152 251/2939 6.60174269183974e-06 0.00036045515097445 0.000316883649208308 DSP/ALB/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/CAT/EEF2/TUBB4B/LYZ/CTSD/DMBT1/SOD1/GSTP1/ALDOA/CAPN1/VCL/SERPINA3/LCN2/GSN/AGA/PNP/LAMP1/LAMP2/S100A11/GDI2/NPC2 30 +GO:0101002 ficolin-1-rich granule 14/152 72/2939 1.18733421290438e-05 0.000540237066871494 0.000474933685161753 DSP/DSG1/JUP/CAT/EEF2/CTSD/GSTP1/ALDOA/CAPN1/VCL/GSN/PNP/LAMP1/LAMP2 14 +GO:0005766 primary lysosome 12/152 61/2939 4.56978270565284e-05 0.00143685132139962 0.00126316599683483 ANXA2/SERPINB3/FABP5/PIGR/TUBB4B/LYZ/SERPINA3/AGA/LAMP1/LAMP2/GDI2/NPC2 12 +GO:0042582 azurophil granule 12/152 61/2939 4.56978270565284e-05 0.00143685132139962 0.00126316599683483 ANXA2/SERPINB3/FABP5/PIGR/TUBB4B/LYZ/SERPINA3/AGA/LAMP1/LAMP2/GDI2/NPC2 12 +GO:0031012 extracellular matrix 17/152 113/2939 4.73687248813062e-05 0.00143685132139962 0.00126316599683483 DSP/DSG1/ANXA2/JUP/PLEC/LMNA/HSPA5/CSTA/GAPDH/EEF2/MYH9/TUBB4B/CTSD/FLNB/SOD1/HSPB1/ATP5A1 17 +GO:0005882 intermediate filament 7/152 21/2939 5.43339859285434e-05 0.00148331781584923 0.00130401566228504 DSP/KRT6A/JUP/KRT17/KRT6B/LMNA/KRT15 7 +GO:0035578 azurophil granule lumen 9/152 39/2939 0.000116381481601412 0.00288837677065322 0.00253923232584899 ANXA2/SERPINB3/FABP5/TUBB4B/LYZ/SERPINA3/AGA/GDI2/NPC2 9 +GO:0045111 intermediate filament cytoskeleton 8/152 32/2939 0.000154925405587284 0.00352455297711071 0.00309850811174568 DSP/KRT6A/JUP/KRT17/PLEC/KRT6B/LMNA/KRT15 8 +GO:1904813 ficolin-1-rich granule lumen 10/152 53/2939 0.000289825905131926 0.00573615147717977 0.00504277052938881 JUP/CAT/EEF2/CTSD/GSTP1/ALDOA/CAPN1/VCL/GSN/PNP 10 +GO:0005775 vacuolar lumen 11/152 63/2939 0.000294161614214347 0.00573615147717977 0.00504277052938881 ANXA2/SERPINB3/FABP5/TUBB4B/LYZ/CTSD/SERPINA3/AGA/LAMP2/GDI2/NPC2 11 +GO:0001533 cornified envelope 5/152 13/2939 0.000318245371505049 0.00579206576139188 0.00509192594408078 DSP/DSG1/JUP/ANXA1/CSTA 5 +GO:0044433 cytoplasmic vesicle part 32/152 338/2939 0.000357212587465447 0.00590003159894176 0.00518684096610265 DSP/ALB/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/ANXA1/CAT/SFN/EEF2/TUBB4B/LYZ/CTSD/UBA52/DMBT1/GSTP1/ALDOA/CAPN1/VCL/SERPINA3/LCN2/GSN/AGA/PNP/LAMP1/LAMP2/S100A11/GDI2/NPC2 32 +GO:0035580 specific granule lumen 6/152 20/2939 0.000367401235098937 0.00590003159894176 0.00518684096610265 JUP/LTF/LYZ/CTSD/VCL/LCN2 6
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/cluster_profiler_EGO_MF.csv Tue Dec 18 09:21:32 2018 -0500 @@ -0,0 +1,2 @@ +x +No Go terms enriched (EGO) found for MF ontology
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/cluster_profiler_GGO_BP.csv Tue Dec 18 09:21:32 2018 -0500 @@ -0,0 +1,586 @@ +ID Description Count GeneRatio geneID +GO:0019953 sexual reproduction 3 3/153 SOD1/CTSV/ALDOA +GO:0019954 asexual reproduction 0 0/153 +GO:0022414 reproductive process 10 10/153 DSG1/ANXA1/ARG1/MYH9/SOD1/CTSV/ALDOA/SERPINB5/CTSB/ACTR2 +GO:0032504 multicellular organism reproduction 6 6/153 DSG1/ANXA1/ARG1/SOD1/CTSV/CTSB +GO:0032505 reproduction of a single-celled organism 0 0/153 +GO:0061887 reproduction of symbiont in host 0 0/153 +GO:0055114 oxidation-reduction process 16 16/153 ENO1/CAT/PKM/TPI1/PRDX1/GAPDH/LDHA/UBA52/TXN/SOD1/ALOX12B/PGK1/ALDOA/MDH2/ALDOC/APOD +GO:0006807 nitrogen compound metabolic process 105 105/153 DSP/ALB/ANXA2/JUP/LTF/MUC5B/SERPINB3/KRT17/FABP5/CASP14/ENO1/AZGP1/TGM3/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/SERPINB7/LYZ/SERPINA1/HSP90AA1/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/CPA4/BLMH/PLBD1/SOD1/HSPB1/HSPA8/EIF4A1/PPIA/YWHAZ/GGH/ALOX12B/GSTP1/LCN1/SERPINB4/C1orf68/CTSV/PGK1/ALDOA/CAPN1/YWHAE/HBB/A2ML1/SERPINA3/SPRR1B/SERPINB1/CST6/GSN/IDE/AGA/PSMA3/EEF1G/SERPINB5/MDH2/LYPD3/PNP/CSTB/ALDOC/FLG/PERP/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP2/TYMP/PPIB/RPS3/ATP5A1/S100A11/HAL/GSS/PSMB3/PIP/CST4/MUC7/CST1/CST2/KRT1/KRT2/KRT10/SERPINA12/DCD/SPRR2E +GO:0009056 catabolic process 41 41/153 ANXA2/FABP5/ENO1/HSPA5/CAT/SERPINB12/PKM/TPI1/PRDX1/ARG1/GAPDH/HSPA1A/HSPA1B/LYZ/HSP90AA1/LDHA/CTSD/UBA52/BLMH/PLBD1/HSPB1/HSPA8/EIF4A1/YWHAZ/CTSV/PGK1/ALDOA/CAPN1/HBB/HP/IDE/PSMA3/PNP/ALDOC/CTSB/RPSA/LAMP2/TYMP/RPS3/HAL/PSMB3 +GO:0009058 biosynthetic process 47 47/153 JUP/LTF/MUC5B/KRT17/FABP5/ENO1/ANXA1/HSPA5/CAT/PKM/TPI1/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/SERPINB7/HSP90AA1/ACTN4/GGCT/UBA52/TXN/SOD1/HSPB1/HSPA8/EIF4A1/PPIA/ALOX12B/GSTP1/PGK1/ALDOA/HBB/PSMA3/EEF1G/MDH2/LYPD3/PNP/ALDOC/RPSA/TYMP/RPS3/ATP5A1/S100A11/GSS/PSMB3/MUC7/SERPINA12 +GO:0009892 negative regulation of metabolic process 42 42/153 ANXA2/LTF/SERPINB3/ENO1/SFN/SERPINB12/CSTA/GAPDH/HSPA1A/HSPA1B/SERPINB7/SERPINA1/UBA52/TXN/SOD1/HSPB1/HSPA8/EIF4A1/YWHAZ/GSTP1/LCN1/SERPINB4/YWHAE/A2ML1/HP/SERPINA3/SERPINB1/CST6/IDE/PSMA3/SERPINB5/CSTB/SERPINB13/APOD/RPSA/RPS3/S100A11/PSMB3/CST4/CST1/CST2/SERPINA12 +GO:0009893 positive regulation of metabolic process 31 31/153 ANXA2/LTF/SERPINB3/KRT17/ENO1/LMNA/ANXA1/HSPA5/S100A7/HSPA1A/HSPA1B/EEF2/MYH9/SERPINB7/HSP90AA1/UBA52/TXN/SOD1/HSPB1/HSPA8/ALOX12B/GSTP1/HBB/LCN2/GSN/IDE/PSMA3/PERP/RPS3/PSMB3/PIP +GO:0018933 nicotine metabolic process 0 0/153 +GO:0019222 regulation of metabolic process 62 62/153 ANXA2/JUP/LTF/SERPINB3/KRT17/ENO1/LMNA/ANXA1/HSPA5/CAT/S100A7/SFN/SERPINB12/PRDX1/CSTA/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/SERPINB7/SERPINA1/HSP90AA1/ACTN4/UBA52/TXN/SOD1/HSPB1/HSPA8/EIF4A1/YWHAZ/ALOX12B/GSTP1/LCN1/SERPINB4/CAPN1/YWHAE/HBB/A2ML1/HP/SERPINA3/SERPINB1/LCN2/CST6/GSN/IDE/PSMA3/SERPINB5/CSTB/PERP/SERPINB13/APOD/RPSA/RPS3/S100A11/PSMB3/NPC2/PIP/CST4/CST1/CST2/SERPINA12 +GO:0019694 alkanesulfonate metabolic process 0 0/153 +GO:0019748 secondary metabolic process 0 0/153 +GO:0032259 methylation 2 2/153 EEF2/HSPA8 +GO:0042440 pigment metabolic process 0 0/153 +GO:0042445 hormone metabolic process 1 1/153 IDE +GO:0044033 multi-organism metabolic process 1 1/153 ANXA2 +GO:0044236 multicellular organism metabolic process 4 4/153 ARG1/SERPINB7/CTSD/CTSB +GO:0044237 cellular metabolic process 103 103/153 DSP/ALB/ANXA2/JUP/LTF/MUC5B/SERPINB3/KRT17/FABP5/ENO1/AZGP1/TGM3/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/SERPINB7/LYZ/SERPINA1/HSP90AA1/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/CPA4/BLMH/PLBD1/SOD1/HSPB1/HSPA8/EIF4A1/PPIA/YWHAZ/GGH/ALOX12B/GSTP1/LCN1/SERPINB4/C1orf68/CTSV/PGK1/ALDOA/CAPN1/YWHAE/HBB/A2ML1/HP/SERPINA3/SPRR1B/SERPINB1/CST6/GSN/IDE/AGA/PSMA3/EEF1G/SERPINB5/MDH2/LYPD3/PNP/CSTB/ALDOC/FLG/PERP/SERPINB13/APOD/CTSB/RPSA/LAMP2/TYMP/PPIB/RPS3/ATP5A1/S100A11/HAL/GSS/PSMB3/NPC2/CST4/MUC7/CST1/CST2/KRT1/KRT2/KRT10/SERPINA12/SPRR2E +GO:0044238 primary metabolic process 108 108/153 DSP/ALB/ANXA2/JUP/LTF/MUC5B/SERPINB3/KRT17/FABP5/CASP14/ENO1/AZGP1/TGM3/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/SERPINB7/LYZ/SERPINA1/HSP90AA1/ACTN4/LDHA/CTSD/UBA52/TXN/DMBT1/CPA4/BLMH/PLBD1/SOD1/HSPB1/HSPA8/EIF4A1/PPIA/YWHAZ/GGH/ALOX12B/GSTP1/LCN1/SERPINB4/C1orf68/CTSV/PGK1/ALDOA/CAPN1/YWHAE/A2ML1/SERPINA3/IL1RN/SPRR1B/SERPINB1/CST6/GSN/IDE/AGA/PSMA3/EEF1G/SERPINB5/MDH2/LYPD3/PNP/CSTB/ALDOC/FLG/PERP/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP2/TYMP/PPIB/RPS3/ATP5A1/S100A11/HAL/GSS/PSMB3/NPC2/AMY1A/AMY1B/AMY1C/PIP/CST4/MUC7/CST1/CST2/KRT1/KRT2/KRT10/SERPINA12/DCD/SPRR2E +GO:0044281 small molecule metabolic process 32 32/153 FABP5/ENO1/ANXA1/CAT/PKM/TPI1/ARG1/GAPDH/HSPA1A/HSPA1B/LDHA/TXN/BLMH/SOD1/HSPA8/GGH/ALOX12B/GSTP1/PGK1/ALDOA/PSMA3/MDH2/PNP/ALDOC/APOD/TYMP/ATP5A1/HAL/GSS/PSMB3/NPC2/SERPINA12 +GO:0045730 respiratory burst 0 0/153 +GO:0070085 glycosylation 2 2/153 MUC5B/MUC7 +GO:0070988 demethylation 0 0/153 +GO:0071704 organic substance metabolic process 110 110/153 DSP/ALB/ANXA2/JUP/LTF/MUC5B/SERPINB3/KRT17/FABP5/CASP14/ENO1/AZGP1/TGM3/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/SERPINB7/LYZ/SERPINA1/HSP90AA1/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/CPA4/BLMH/PLBD1/SOD1/HSPB1/HSPA8/EIF4A1/PPIA/YWHAZ/GGH/ALOX12B/GSTP1/LCN1/SERPINB4/C1orf68/CTSV/PGK1/ALDOA/CAPN1/YWHAE/A2ML1/SERPINA3/IL1RN/SPRR1B/SERPINB1/LCN2/CST6/GSN/IDE/AGA/PSMA3/EEF1G/SERPINB5/MDH2/LYPD3/PNP/CSTB/ALDOC/FLG/PERP/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP2/TYMP/PPIB/RPS3/ATP5A1/S100A11/HAL/GSS/PSMB3/NPC2/AMY1A/AMY1B/AMY1C/PIP/CST4/MUC7/CST1/CST2/KRT1/KRT2/KRT10/SERPINA12/DCD/SPRR2E +GO:1900872 pentadec-1-ene metabolic process 0 0/153 +GO:1901049 atropine metabolic process 0 0/153 +GO:1901275 tartrate metabolic process 0 0/153 +GO:1901902 tyrocidine metabolic process 0 0/153 +GO:1902421 hydrogen metabolic process 0 0/153 +GO:0001909 leukocyte mediated cytotoxicity 5 5/153 PRDX1/ARG1/TUBB4B/SERPINB4/LAMP1 +GO:0031341 regulation of cell killing 4 4/153 ARG1/GAPDH/SERPINB4/LAMP1 +GO:0031342 negative regulation of cell killing 1 1/153 SERPINB4 +GO:0031343 positive regulation of cell killing 3 3/153 ARG1/GAPDH/LAMP1 +GO:0031640 killing of cells of other organism 8 8/153 ALB/LTF/ARG1/GAPDH/LYZ/MUC7/DCD/DEFA3 +GO:0097278 complement-dependent cytotoxicity 0 0/153 +GO:0001776 leukocyte homeostasis 1 1/153 ANXA1 +GO:0002200 somatic diversification of immune receptors 0 0/153 +GO:0002252 immune effector process 57 57/153 DSP/DSG1/ANXA2/JUP/LTF/SERPINB3/ACTG1/FABP5/PIGR/HRNR/ANXA1/CAT/S100A7/SERPINB12/PKM/PRDX1/ARG1/HSPA1A/HSPA1B/EEF2/TUBB4B/LYZ/SERPINA1/HSP90AA1/CTSD/DMBT1/HSPA8/PPIA/GGH/GSTP1/SERPINB4/ALDOA/CAPN1/VCL/HBB/HP/SERPINA3/ORM1/SERPINB1/LCN2/GSN/AGA/PNP/CSTB/ALDOC/CTSB/LAMP1/LAMP2/S100A11/GDI2/ARPC4/ACTR2/NPC2/CALML5/KRT1/FLG2/DEFA3 +GO:0002253 activation of immune response 17 17/153 LTF/MUC5B/ACTG1/HSPA1A/HSPA1B/HSP90AA1/UBA52/DMBT1/S100A14/PSMA3/CTSB/RPS3/PSMB3/ARPC4/ACTR2/MUC7/KRT1 +GO:0002262 myeloid cell homeostasis 3 3/153 ANXA1/PRDX1/SOD1 +GO:0002339 B cell selection 0 0/153 +GO:0002404 antigen sampling in mucosal-associated lymphoid tissue 0 0/153 +GO:0002440 production of molecular mediator of immune response 1 1/153 ARG1 +GO:0002507 tolerance induction 0 0/153 +GO:0002520 immune system development 11 11/153 ANXA2/LTF/ANXA1/SERPINB12/EEF2/MYH9/UBA52/SOD1/PSMA3/PNP/PSMB3 +GO:0002682 regulation of immune system process 29 29/153 LTF/MUC5B/ACTG1/PIGR/ANXA1/S100A7/ARG1/HSPA1A/HSPA1B/HSP90AA1/UBA52/DMBT1/SOD1/SERPINB4/ORM1/S100A14/GSN/PSMA3/PNP/APOD/CTSB/LAMP1/RPS3/PSMB3/ARPC4/ACTR2/PIP/MUC7/KRT1 +GO:0002683 negative regulation of immune system process 5 5/153 LTF/ANXA1/ARG1/SERPINB4/APOD +GO:0002684 positive regulation of immune system process 22 22/153 LTF/MUC5B/ACTG1/ANXA1/S100A7/ARG1/HSPA1A/HSPA1B/HSP90AA1/UBA52/DMBT1/S100A14/PSMA3/PNP/CTSB/LAMP1/RPS3/PSMB3/ARPC4/ACTR2/MUC7/KRT1 +GO:0006955 immune response 69 69/153 DSP/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/FABP5/PIGR/HRNR/ANXA1/CAT/S100A7/SERPINB12/PKM/PRDX1/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/TUBB4B/LYZ/SERPINA1/HSP90AA1/IL36G/CTSD/UBA52/DMBT1/HSPA8/PPIA/GGH/GSTP1/SERPINB4/ALDOA/CAPN1/VCL/HBB/HP/SERPINA3/ORM1/IL1RN/SERPINB1/LCN2/S100A14/GSN/AGA/PSMA3/PNP/CSTB/ALDOC/CTSB/LAMP1/LAMP2/RPS3/S100A11/PSMB3/GDI2/ARPC4/ACTR2/NPC2/CALML5/MUC7/KRT1/FLG2/DCD/DEFA3 +GO:0019882 antigen processing and presentation 5 5/153 CTSD/CTSV/PSMA3/CAPZB/PSMB3 +GO:0031294 lymphocyte costimulation 0 0/153 +GO:0035172 hemocyte proliferation 0 0/153 +GO:0042386 hemocyte differentiation 0 0/153 +GO:0045058 T cell selection 0 0/153 +GO:0045321 leukocyte activation 55 55/153 DSP/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/HRNR/ANXA1/CAT/S100A7/SERPINB12/PKM/PRDX1/ARG1/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/LYZ/SERPINA1/HSP90AA1/CTSD/SOD1/HSPA8/PPIA/GGH/GSTP1/ALDOA/CAPN1/VCL/HBB/HP/SERPINA3/ORM1/SERPINB1/LCN2/GSN/AGA/PNP/CSTB/ALDOC/CTSB/LAMP1/LAMP2/RPS3/S100A11/GDI2/ACTR2/NPC2/CALML5/KRT1/FLG2 +GO:0050900 leukocyte migration 6 6/153 ANXA1/S100A7/MYH9/PPIA/S100A14/APOD +GO:0090713 immunological memory process 0 0/153 +GO:0006792 regulation of sulfur utilization 0 0/153 +GO:0045882 negative regulation of sulfur utilization 0 0/153 +GO:0045883 positive regulation of sulfur utilization 0 0/153 +GO:0006795 regulation of phosphorus utilization 0 0/153 +GO:0045942 negative regulation of phosphorus utilization 0 0/153 +GO:0045949 positive regulation of phosphorus utilization 0 0/153 +GO:0001545 primary ovarian follicle growth 0 0/153 +GO:0001546 preantral ovarian follicle growth 0 0/153 +GO:0001550 ovarian cumulus expansion 0 0/153 +GO:0016049 cell growth 6 6/153 KRT17/ENO1/SFN/HSPA1A/HSPA1B/VCL +GO:0007117 budding cell bud growth 0 0/153 +GO:0030447 filamentous growth 0 0/153 +GO:0040008 regulation of growth 8 8/153 KRT17/ENO1/SFN/HSPA1A/HSPA1B/SOD1/EPPK1/PPIB +GO:0042702 uterine wall growth 0 0/153 +GO:0044110 growth involved in symbiotic interaction 0 0/153 +GO:0045926 negative regulation of growth 3 3/153 ENO1/HSPA1A/HSPA1B +GO:0045927 positive regulation of growth 3 3/153 KRT17/SFN/PPIB +GO:0048589 developmental growth 8 8/153 ANXA1/PKM/SOD1/EPPK1/VCL/GSN/APOD/PPIB +GO:0080189 primary growth 0 0/153 +GO:0080190 lateral growth 0 0/153 +GO:0002209 behavioral defense response 0 0/153 +GO:0002210 behavioral response to wounding 0 0/153 +GO:0007611 learning or memory 1 1/153 ACTR2 +GO:0007622 rhythmic behavior 0 0/153 +GO:0007625 grooming behavior 0 0/153 +GO:0007626 locomotory behavior 2 2/153 SOD1/CSTB +GO:0030537 larval behavior 0 0/153 +GO:0007631 feeding behavior 0 0/153 +GO:0007632 visual behavior 0 0/153 +GO:0007635 chemosensory behavior 0 0/153 +GO:0007638 mechanosensory behavior 0 0/153 +GO:0030534 adult behavior 1 1/153 CSTB +GO:0019098 reproductive behavior 0 0/153 +GO:0032537 host-seeking behavior 0 0/153 +GO:0035187 hatching behavior 0 0/153 +GO:0035640 exploration behavior 0 0/153 +GO:0040040 thermosensory behavior 0 0/153 +GO:0042630 behavioral response to water deprivation 0 0/153 +GO:0048266 behavioral response to pain 0 0/153 +GO:0048520 positive regulation of behavior 0 0/153 +GO:0048521 negative regulation of behavior 0 0/153 +GO:0050795 regulation of behavior 0 0/153 +GO:0051705 multi-organism behavior 0 0/153 +GO:0051780 behavioral response to nutrient 0 0/153 +GO:0051867 general adaptation syndrome, behavioral process 0 0/153 +GO:0060273 crying behavior 0 0/153 +GO:0060756 foraging behavior 0 0/153 +GO:0061744 motor behavior 0 0/153 +GO:0071625 vocalization behavior 0 0/153 +GO:0001833 inner cell mass cell proliferation 0 0/153 +GO:0001834 trophectodermal cell proliferation 0 0/153 +GO:0002174 mammary stem cell proliferation 0 0/153 +GO:0002941 synoviocyte proliferation 0 0/153 +GO:0003419 growth plate cartilage chondrocyte proliferation 0 0/153 +GO:0008284 positive regulation of cell proliferation 9 9/153 ANXA2/LTF/SERPINB3/ANXA1/ARG1/SERPINB7/CAPN1/PNP/RPS3 +GO:0008285 negative regulation of cell proliferation 11 11/153 AZGP1/LMNA/SFN/ARG1/HSPA1A/HSPA1B/EPPK1/GSTP1/APOD/ATP5A1/S100A11 +GO:0010463 mesenchymal cell proliferation 1 1/153 LMNA +GO:0014009 glial cell proliferation 1 1/153 EEF2 +GO:0033002 muscle cell proliferation 2 2/153 GSTP1/APOD +GO:0033687 osteoblast proliferation 1 1/153 LTF +GO:0035726 common myeloid progenitor cell proliferation 1 1/153 GSTP1 +GO:0035736 cell proliferation involved in compound eye morphogenesis 0 0/153 +GO:0035988 chondrocyte proliferation 1 1/153 LTF +GO:0036093 germ cell proliferation 0 0/153 +GO:0042127 regulation of cell proliferation 21 21/153 ANXA2/JUP/LTF/SERPINB3/AZGP1/LMNA/ANXA1/SFN/ARG1/HSPA1A/HSPA1B/SERPINB7/EPPK1/GSTP1/CAPN1/SERPINB5/PNP/APOD/RPS3/ATP5A1/S100A11 +GO:0044340 canonical Wnt signaling pathway involved in regulation of cell proliferation 0 0/153 +GO:0048134 germ-line cyst formation 0 0/153 +GO:0048144 fibroblast proliferation 2 2/153 ANXA2/GSTP1 +GO:0050673 epithelial cell proliferation 6 6/153 SFN/ARG1/EPPK1/SERPINB5/ATP5A1/KRT2 +GO:0051450 myoblast proliferation 0 0/153 +GO:0060722 cell proliferation involved in embryonic placenta development 0 0/153 +GO:0061323 cell proliferation involved in heart morphogenesis 0 0/153 +GO:0061351 neural precursor cell proliferation 0 0/153 +GO:0070341 fat cell proliferation 0 0/153 +GO:0070661 leukocyte proliferation 5 5/153 ANXA1/ARG1/GSTP1/PNP/RPS3 +GO:0071335 hair follicle cell proliferation 0 0/153 +GO:0071838 cell proliferation in bone marrow 0 0/153 +GO:0072089 stem cell proliferation 0 0/153 +GO:0072111 cell proliferation involved in kidney development 1 1/153 SERPINB7 +GO:0090255 cell proliferation involved in imaginal disc-derived wing morphogenesis 0 0/153 +GO:0097360 chorionic trophoblast cell proliferation 0 0/153 +GO:1990654 sebum secreting cell proliferation 0 0/153 +GO:2000793 cell proliferation involved in heart valve development 0 0/153 +GO:0043610 regulation of carbohydrate utilization 0 0/153 +GO:0007059 chromosome segregation 2 2/153 RPS3/ACTR2 +GO:0007017 microtubule-based process 12 12/153 LMNA/GAPDH/HSPA1A/HSPA1B/MYH9/TUBB4B/TUBA1B/SOD1/HSPB1/LAMP1/RPS3/ACTR2 +GO:0000075 cell cycle checkpoint 2 2/153 SFN/UBA52 +GO:0000920 cell separation after cytokinesis 0 0/153 +GO:0001775 cell activation 59 59/153 DSP/DSG1/ANXA2/JUP/LTF/SERPINB3/ACTG1/FABP5/PIGR/HRNR/ANXA1/CAT/S100A7/SERPINB12/PKM/PRDX1/ARG1/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/LYZ/SERPINA1/HSP90AA1/CTSD/SOD1/HSPB1/HSPA8/PPIA/YWHAZ/GGH/GSTP1/ALDOA/CAPN1/VCL/HBB/HP/SERPINA3/ORM1/SERPINB1/LCN2/GSN/AGA/PNP/CSTB/ALDOC/CTSB/LAMP1/LAMP2/RPS3/S100A11/GDI2/ACTR2/NPC2/CALML5/KRT1/KRT2/FLG2 +GO:0010496 intercellular transport 0 0/153 +GO:0006457 protein folding 9 9/153 HSPA5/HSPA1A/HSPA1B/HSP90AA1/UBA52/HSPB1/HSPA8/PPIA/PPIB +GO:0007165 signal transduction 56 56/153 ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT17/PIGR/ENO1/LMNA/ANXA1/HSPA5/CAT/S100A7/SFN/PRDX1/ARG1/HSPA1A/HSPA1B/MYH9/HSP90AA1/IL36G/ACTN4/GGCT/UBA52/TXN/DMBT1/FLNB/SOD1/HSPB1/PPIA/YWHAZ/ALOX12B/GSTP1/YWHAE/IL1RN/LCN2/S100A14/GSN/IDE/PSMA3/PERP/APOD/CTSB/LAMP1/TYMP/RPS3/S100A11/PSMB3/GDI2/ARPC4/ACTR2/CALML5/MUC7/SERPINA12/DEFA3 +GO:0006903 vesicle targeting 1 1/153 SERPINA1 +GO:0006276 plasmid maintenance 0 0/153 +GO:0006928 movement of cell or subcellular component 28 28/153 DSP/KRT16/JUP/SERPINB3/ACTG1/LMNA/ANXA1/HSPA5/S100A7/MYH9/TUBB4B/ACTN4/TXN/SOD1/HSPB1/EPPK1/PPIA/GSTP1/VCL/YWHAE/S100A14/SERPINB5/APOD/LAMP1/ATP5A1/CAPZB/ACTR2/KRT2 +GO:0006949 syncytium formation 1 1/153 MYH9 +GO:0007049 cell cycle 15 15/153 LMNA/ANXA1/SFN/HSPA1A/HSPA1B/MYH9/TUBB4B/HSP90AA1/UBA52/HSPA8/YWHAE/PSMA3/RPS3/PSMB3/ACTR2 +GO:0007154 cell communication 61 61/153 DSP/ALB/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT17/PIGR/ENO1/LMNA/ANXA1/HSPA5/CAT/S100A7/SFN/PRDX1/ARG1/HSPA1A/HSPA1B/MYH9/HSP90AA1/IL36G/ACTN4/GGCT/UBA52/TXN/DMBT1/FLNB/SOD1/HSPB1/HSPA8/PPIA/YWHAZ/ALOX12B/GSTP1/CTSV/YWHAE/IL1RN/LCN2/S100A14/GSN/IDE/PSMA3/PERP/APOD/CTSB/LAMP1/LAMP2/TYMP/RPS3/S100A11/PSMB3/GDI2/ARPC4/ACTR2/CALML5/MUC7/SERPINA12/DEFA3 +GO:0007163 establishment or maintenance of cell polarity 4 4/153 LMNA/MYH9/GSN/ACTR2 +GO:0007272 ensheathment of neurons 2 2/153 SOD1/TYMP +GO:0008219 cell death 58 58/153 DSP/KRT6A/ALB/KRT16/DSG1/JUP/LTF/KRT78/KRT17/CASP14/ENO1/KRT80/KRT13/KRT6B/LMNA/ANXA1/HSPA5/CAT/SFN/PKM/CSTA/GAPDH/HSPA1A/HSPA1B/ACTN4/GGCT/LDHA/UBA52/TXN/LGALS7B/SOD1/HSPB1/YWHAZ/GSTP1/DSC3/CTSV/CAPN1/YWHAE/HBB/KRT23/HP/SPRR1B/LCN2/S100A14/GSN/KRT15/FLG/PERP/SERPINB13/CTSB/LAMP1/RPS3/PIP/KRT1/KRT2/KRT10/SPRR2E/KRT85 +GO:0008037 cell recognition 1 1/153 ALDOA +GO:0019835 cytolysis 2 2/153 ALB/LYZ +GO:0010118 stomatal movement 0 0/153 +GO:0016037 light absorption 0 0/153 +GO:0016043 cellular component organization 65 65/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/ACTG1/KRT17/ENO1/PLEC/TGM3/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/TF/CAT/SFN/PKM/ARG1/GAPDH/HSPA1A/HSPA1B/MYH9/TUBB4B/POF1B/TUBA1B/SERPINA1/HSP90AA1/ACTN4/GGCT/UBA52/CPA4/FLNB/SOD1/HSPA8/EPPK1/PPIA/YWHAZ/CTSV/ALDOA/CAPN1/VCL/YWHAE/HBB/LCN2/GSN/IDE/SERPINB5/KRT15/PERP/APOD/RPSA/LAMP2/TYMP/RPS3/ATP5A1/CAPG/CAPZB/ARPC4/ACTR2/KRT2 +GO:0016458 gene silencing 0 0/153 +GO:0019725 cellular homeostasis 11 11/153 LTF/TF/PRDX1/UBA52/TXN/SOD1/ALDOA/YWHAE/LCN2/IDE/LAMP2 +GO:0022402 cell cycle process 14 14/153 LMNA/ANXA1/SFN/HSPA1A/HSPA1B/MYH9/TUBB4B/HSP90AA1/UBA52/YWHAE/PSMA3/RPS3/PSMB3/ACTR2 +GO:0022406 membrane docking 3 3/153 TUBB4B/HSP90AA1/YWHAE +GO:0022412 cellular process involved in reproduction in multicellular organism 0 0/153 +GO:0030029 actin filament-based process 14 14/153 DSP/JUP/ACTG1/ANXA1/MYH9/POF1B/ACTN4/FLNB/ALDOA/GSN/CAPG/CAPZB/ARPC4/ACTR2 +GO:0032196 transposition 0 0/153 +GO:0032940 secretion by cell 57 57/153 DSP/ALB/DSG1/ANXA2/JUP/LTF/SERPINB3/FABP5/PIGR/HRNR/ANXA1/TF/CAT/S100A7/SERPINB12/PKM/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/TUBB4B/LYZ/SERPINA1/HSP90AA1/ACTN4/CTSD/SOD1/HSPA8/PPIA/GGH/GSTP1/ALDOA/CAPN1/VCL/HBB/HP/SERPINA3/ORM1/IL1RN/SERPINB1/LCN2/GSN/AGA/PNP/CSTB/ALDOC/CTSB/LAMP1/LAMP2/S100A11/GDI2/ACTR2/NPC2/CALML5/KRT1/FLG2 +GO:0033059 cellular pigmentation 0 0/153 +GO:0034337 RNA folding 0 0/153 +GO:0035212 cell competition in a multicellular organism 0 0/153 +GO:0035638 signal maturation 0 0/153 +GO:0036166 phenotypic switching 0 0/153 +GO:0043335 protein unfolding 1 1/153 HSP90AA1 +GO:0044663 establishment or maintenance of cell type involved in phenotypic switching 0 0/153 +GO:0044764 multi-organism cellular process 3 3/153 ALB/LTF/PPIA +GO:0045103 intermediate filament-based process 7 7/153 DSP/KRT6A/KRT16/KRT17/SOD1/EPPK1/KRT2 +GO:0048522 positive regulation of cellular process 51 51/153 ANXA2/JUP/LTF/SERPINB3/KRT17/ENO1/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/SERPINB7/HSP90AA1/ACTN4/LDHA/UBA52/TXN/SOD1/HSPB1/HSPA8/PPIA/YWHAZ/ALOX12B/GSTP1/CAPN1/YWHAE/HBB/HP/ORM1/LCN2/S100A14/GSN/IDE/PSMA3/PNP/PERP/LAMP1/RPS3/ATP5A1/PSMB3/ARPC4/ACTR2/SERPINA12 +GO:0048523 negative regulation of cellular process 58 58/153 ALB/KRT16/ANXA2/LTF/SERPINB3/ENO1/AZGP1/LMNA/ANXA1/HSPA5/CAT/SFN/SERPINB12/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/MYH9/SERPINB7/SERPINA1/ACTN4/UBA52/TXN/SOD1/HSPB1/HSPA8/EPPK1/YWHAZ/GSTP1/LCN1/SERPINB4/VCL/YWHAE/A2ML1/HP/SERPINA3/IL1RN/SERPINB1/CST6/GSN/IDE/PSMA3/SERPINB5/CSTB/SERPINB13/APOD/RPS3/ATP5A1/S100A11/CAPG/CAPZB/PSMB3/PIP/CST4/CST1/CST2/SERPINA12 +GO:0048869 cellular developmental process 63 63/153 DSP/KRT6A/KRT16/DSG1/ANXA2/JUP/LTF/SERPINB3/ACTG1/KRT78/KRT17/CASP14/KRT80/TGM3/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/CAT/S100A7/SFN/SERPINB12/CSTA/EEF2/MYH9/POF1B/ACTN4/UBA52/DMBT1/FLNB/SOD1/GSTP1/DSC3/C1orf68/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/KRT23/SPRR1B/GSN/PSMA3/PNP/ALDOC/KRT15/FLG/PERP/SERPINB13/APOD/CTSB/TYMP/CAPZB/PSMB3/ACTR2/KRT1/KRT2/KRT10/SPRR2E/KRT85 +GO:0050794 regulation of cellular process 96 96/153 DSP/ALB/KRT16/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT17/PIGR/ENO1/AZGP1/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/SERPINB7/SERPINA1/HSP90AA1/IL36G/ACTN4/GGCT/LDHA/UBA52/TXN/DMBT1/FLNB/SOD1/HSPB1/HSPA8/EPPK1/PPIA/YWHAZ/ALOX12B/GSTP1/LCN1/SERPINB4/CTSV/ALDOA/CAPN1/VCL/YWHAE/HBB/A2ML1/HP/SERPINA3/ORM1/IL1RN/SERPINB1/LCN2/CST6/S100A14/GSN/IDE/PSMA3/SERPINB5/PNP/CSTB/PERP/SERPINB13/APOD/CTSB/LAMP1/TYMP/RPS3/ATP5A1/S100A11/CAPG/CAPZB/PSMB3/GDI2/ARPC4/ACTR2/NPC2/CALML5/PIP/CST4/MUC7/CST1/CST2/SERPINA12/DEFA3 +GO:0051301 cell division 6 6/153 CAT/SFN/MYH9/TUBA1B/RPS3/ACTR2 +GO:0051651 maintenance of location in cell 5 5/153 ALB/JUP/HSPA5/FLNB/GSN +GO:0051716 cellular response to stimulus 69 69/153 ALB/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT17/PIGR/ENO1/KRT13/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/PKM/PRDX1/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBA1B/HSP90AA1/IL36G/ACTN4/GGCT/UBA52/TXN/DMBT1/FLNB/SOD1/HSPB1/HSPA8/PPIA/YWHAZ/ALOX12B/GSTP1/CTSV/PGK1/YWHAE/HBB/HP/IL1RN/LCN2/S100A14/GSN/IDE/PSMA3/PERP/APOD/CTSB/LAMP1/LAMP2/TYMP/RPS3/S100A11/PSMB3/GDI2/ARPC4/ACTR2/CALML5/MUC7/SERPINA12/DEFA3 +GO:0060242 contact inhibition 0 0/153 +GO:0060352 cell adhesion molecule production 0 0/153 +GO:0061919 process utilizing autophagic mechanism 8 8/153 GAPDH/HSP90AA1/CTSD/UBA52/HSPB1/HSPA8/CAPN1/LAMP2 +GO:0071554 cell wall organization or biogenesis 1 1/153 LYZ +GO:0071804 cellular potassium ion transport 1 1/153 YWHAE +GO:0090485 chromosome number maintenance 0 0/153 +GO:0090618 DNA clamp unloading 0 0/153 +GO:0097194 execution phase of apoptosis 2 2/153 CASP14/RPS3 +GO:0097528 execution phase of necroptosis 0 0/153 +GO:0140029 exocytic process 0 0/153 +GO:0043609 regulation of carbon utilization 0 0/153 +GO:0006808 regulation of nitrogen utilization 0 0/153 +GO:0019676 ammonia assimilation cycle 0 0/153 +GO:0045847 negative regulation of nitrogen utilization 0 0/153 +GO:0045848 positive regulation of nitrogen utilization 0 0/153 +GO:0000728 gene conversion at mating-type locus, DNA double-strand break formation 0 0/153 +GO:0000734 gene conversion at mating-type locus, DNA repair synthesis 0 0/153 +GO:0000742 karyogamy involved in conjugation with cellular fusion 0 0/153 +GO:0000743 nuclear migration involved in conjugation with cellular fusion 0 0/153 +GO:0000749 response to pheromone involved in conjugation with cellular fusion 0 0/153 +GO:0000751 mitotic cell cycle G1 arrest in response to pheromone 0 0/153 +GO:0000754 adaptation of signaling pathway by response to pheromone involved in conjugation with cellular fusion 0 0/153 +GO:0002077 acrosome matrix dispersal 0 0/153 +GO:0003006 developmental process involved in reproduction 5 5/153 ANXA1/SOD1/CTSV/SERPINB5/CTSB +GO:0007299 ovarian follicle cell-cell adhesion 0 0/153 +GO:0007300 ovarian nurse cell to oocyte transport 0 0/153 +GO:0007303 cytoplasmic transport, nurse cell to oocyte 0 0/153 +GO:0007316 pole plasm RNA localization 0 0/153 +GO:0007318 pole plasm protein localization 0 0/153 +GO:0007340 acrosome reaction 0 0/153 +GO:0007343 egg activation 0 0/153 +GO:0007344 pronuclear fusion 0 0/153 +GO:0007534 gene conversion at mating-type locus 0 0/153 +GO:0007543 sex determination, somatic-gonadal interaction 0 0/153 +GO:0007566 embryo implantation 1 1/153 SOD1 +GO:0009566 fertilization 1 1/153 ALDOA +GO:0009846 pollen germination 0 0/153 +GO:0009856 pollination 0 0/153 +GO:0009859 pollen hydration 0 0/153 +GO:0009875 pollen-pistil interaction 0 0/153 +GO:0009876 pollen adhesion 0 0/153 +GO:0010069 zygote asymmetric cytokinesis in embryo sac 0 0/153 +GO:0010183 pollen tube guidance 0 0/153 +GO:0010344 seed oilbody biogenesis 0 0/153 +GO:0010588 cotyledon vascular tissue pattern formation 0 0/153 +GO:0010708 heteroduplex formation involved in gene conversion at mating-type locus 0 0/153 +GO:0018985 pronuclear envelope synthesis 0 0/153 +GO:0022413 reproductive process in single-celled organism 0 0/153 +GO:0022602 ovulation cycle process 1 1/153 SOD1 +GO:0030709 border follicle cell delamination 0 0/153 +GO:0030720 oocyte localization involved in germarium-derived egg chamber formation 0 0/153 +GO:0031292 gene conversion at mating-type locus, DNA double-strand break processing 0 0/153 +GO:0032005 signal transduction involved in conjugation with cellular fusion 0 0/153 +GO:0032219 cell wall macromolecule catabolic process involved in cytogamy 0 0/153 +GO:0032220 plasma membrane fusion involved in cytogamy 0 0/153 +GO:0034624 DNA recombinase assembly involved in gene conversion at mating-type locus 0 0/153 +GO:0034636 strand invasion involved in gene conversion at mating-type locus 0 0/153 +GO:0035036 sperm-egg recognition 1 1/153 ALDOA +GO:0035037 sperm entry 0 0/153 +GO:0035038 female pronucleus assembly 0 0/153 +GO:0035039 male pronucleus assembly 0 0/153 +GO:0035040 sperm nuclear envelope removal 0 0/153 +GO:0035041 sperm chromatin decondensation 0 0/153 +GO:0035042 fertilization, exchange of chromosomal proteins 0 0/153 +GO:0035044 sperm aster formation 0 0/153 +GO:0035046 pronuclear migration 0 0/153 +GO:0043093 FtsZ-dependent cytokinesis 0 0/153 +GO:0044703 multi-organism reproductive process 6 6/153 DSG1/ARG1/SOD1/CTSV/ALDOA/CTSB +GO:0045450 bicoid mRNA localization 0 0/153 +GO:0045729 respiratory burst at fertilization 0 0/153 +GO:0046595 establishment of pole plasm mRNA localization 0 0/153 +GO:0048359 mucilage metabolic process involved in seed coat development 0 0/153 +GO:0048497 maintenance of floral organ identity 0 0/153 +GO:0048544 recognition of pollen 0 0/153 +GO:0048573 photoperiodism, flowering 0 0/153 +GO:0048609 multicellular organismal reproductive process 6 6/153 DSG1/ANXA1/ARG1/SOD1/CTSV/CTSB +GO:0051037 regulation of transcription involved in meiotic cell cycle 0 0/153 +GO:0051321 meiotic cell cycle 2 2/153 MYH9/ACTR2 +GO:0051663 oocyte nucleus localization involved in oocyte dorsal/ventral axis specification 0 0/153 +GO:0060011 Sertoli cell proliferation 0 0/153 +GO:0060466 activation of meiosis involved in egg activation 0 0/153 +GO:0060468 prevention of polyspermy 0 0/153 +GO:0060469 positive regulation of transcription involved in egg activation 0 0/153 +GO:0060470 positive regulation of cytosolic calcium ion concentration involved in egg activation 0 0/153 +GO:0060471 cortical granule exocytosis 0 0/153 +GO:0060474 positive regulation of flagellated sperm motility involved in capacitation 0 0/153 +GO:0060475 positive regulation of actin filament polymerization involved in acrosome reaction 0 0/153 +GO:0060476 protein localization involved in acrosome reaction 0 0/153 +GO:0060478 acrosomal vesicle exocytosis 0 0/153 +GO:0060518 cell migration involved in prostatic bud elongation 0 0/153 +GO:0060519 cell adhesion involved in prostatic bud elongation 0 0/153 +GO:0060673 cell-cell signaling involved in placenta development 0 0/153 +GO:0060710 chorio-allantoic fusion 0 0/153 +GO:0060738 epithelial-mesenchymal signaling involved in prostate gland development 0 0/153 +GO:0060739 mesenchymal-epithelial cell signaling involved in prostate gland development 0 0/153 +GO:0060767 epithelial cell proliferation involved in prostate gland development 0 0/153 +GO:0060781 mesenchymal cell proliferation involved in prostate gland development 0 0/153 +GO:0060783 mesenchymal smoothened signaling pathway involved in prostate gland development 0 0/153 +GO:0060858 vesicle-mediated transport involved in floral organ abscission 0 0/153 +GO:0060869 transmembrane receptor protein serine/threonine kinase signaling pathway involved in floral organ abscission 0 0/153 +GO:0060870 cell wall disassembly involved in floral organ abscission 0 0/153 +GO:0061450 trophoblast cell migration 0 0/153 +GO:0061500 gene conversion at mating-type locus, termination of copy-synthesis 0 0/153 +GO:0061883 clathrin-dependent endocytosis involved in vitellogenesis 0 0/153 +GO:0061948 premature acrosome loss 0 0/153 +GO:0070871 cell wall organization involved in conjugation with cellular fusion 0 0/153 +GO:0070872 plasma membrane organization involved in conjugation with cellular fusion 0 0/153 +GO:0071432 peptide mating pheromone maturation involved in conjugation with cellular fusion 0 0/153 +GO:0071508 activation of MAPK activity involved in conjugation with cellular fusion 0 0/153 +GO:0071509 activation of MAPKK activity involved in conjugation with cellular fusion 0 0/153 +GO:0071510 activation of MAPKKK activity involved in conjugation with cellular fusion 0 0/153 +GO:0071511 inactivation of MAPK activity involved in conjugation with cellular fusion 0 0/153 +GO:0071512 MAPK import into nucleus involved in conjugation with cellular fusion 0 0/153 +GO:0071631 mating pheromone secretion involved in conjugation with cellular fusion 0 0/153 +GO:0071833 peptide pheromone export involved in conjugation with cellular fusion 0 0/153 +GO:0072409 detection of stimulus involved in meiotic cell cycle checkpoint 0 0/153 +GO:0090220 chromosome localization to nuclear envelope involved in homologous chromosome segregation 0 0/153 +GO:1902064 regulation of transcription from RNA polymerase II promoter involved in spermatogenesis 0 0/153 +GO:1902397 detection of stimulus involved in meiotic spindle checkpoint 0 0/153 +GO:1902441 protein localization to meiotic spindle pole body 0 0/153 +GO:1903046 meiotic cell cycle process 2 2/153 MYH9/ACTR2 +GO:2000241 regulation of reproductive process 0 0/153 +GO:2000242 negative regulation of reproductive process 0 0/153 +GO:2000243 positive regulation of reproductive process 0 0/153 +GO:0007155 cell adhesion 26 26/153 DSP/DSG1/ANXA2/JUP/ACTG1/AZGP1/ANXA1/CSTA/ARG1/MYH9/ACTN4/LGALS7B/SOD1/HSPB1/DSC3/VCL/HBB/IL1RN/GSN/LYPD3/PNP/PERP/APOD/RPSA/RPS3/S100A11 +GO:0022608 multicellular organism adhesion 0 0/153 +GO:0044406 adhesion of symbiont to host 1 1/153 LTF +GO:0090675 intermicrovillar adhesion 0 0/153 +GO:0007267 cell-cell signaling 10 10/153 JUP/SERPINB3/ANXA1/IL36G/UBA52/TXN/HSPA8/IL1RN/PSMA3/PSMB3 +GO:0021807 motogenic signaling initiating cell movement in cerebral cortex 0 0/153 +GO:0021837 motogenic signaling involved in postnatal olfactory bulb interneuron migration 0 0/153 +GO:0021838 motogenic signaling involved in interneuron migration from the subpallium to the cortex 0 0/153 +GO:0023051 regulation of signaling 34 34/153 ANXA2/JUP/LTF/SERPINB3/ENO1/LMNA/ANXA1/HSPA5/CAT/S100A7/SFN/PRDX1/ARG1/HSPA1A/HSPA1B/IL36G/ACTN4/UBA52/TXN/SOD1/HSPB1/YWHAZ/ALOX12B/GSTP1/YWHAE/IL1RN/GSN/PSMA3/APOD/TYMP/RPS3/PSMB3/GDI2/SERPINA12 +GO:0023056 positive regulation of signaling 20 20/153 ANXA2/JUP/LTF/CAT/S100A7/SFN/HSPA1A/HSPA1B/ACTN4/UBA52/TXN/SOD1/YWHAZ/ALOX12B/YWHAE/GSN/PSMA3/RPS3/PSMB3/SERPINA12 +GO:0023057 negative regulation of signaling 15 15/153 LTF/SERPINB3/ENO1/LMNA/HSPA5/ARG1/HSPA1A/HSPA1B/UBA52/HSPB1/GSTP1/IL1RN/PSMA3/APOD/PSMB3 +GO:0035636 multi-organism signaling 0 0/153 +GO:0035426 extracellular matrix-cell signaling 0 0/153 +GO:0035637 multicellular organismal signaling 5 5/153 DSP/JUP/SOD1/YWHAE/TYMP +GO:0001503 ossification 2 2/153 LTF/CAT +GO:0001763 morphogenesis of a branching structure 0 0/153 +GO:0001816 cytokine production 15 15/153 LTF/ANXA1/ARG1/GAPDH/HSPA1A/HSPA1B/SERPINB7/UBA52/SOD1/HSPB1/GSTP1/ORM1/PNP/APOD/RPS3 +GO:0002021 response to dietary excess 0 0/153 +GO:0002532 production of molecular mediator involved in inflammatory response 1 1/153 APOD +GO:0003008 system process 21 21/153 DSP/JUP/PIGR/ENO1/AZGP1/LMNA/EEF2/SOD1/LCN1/ALDOA/VCL/YWHAE/HBB/SERPINA3/GSN/TYMP/ACTR2/PIP/CST4/CST1/CST2 +GO:0003053 circadian regulation of heart rate 0 0/153 +GO:0007275 multicellular organism development 72 72/153 DSP/KRT6A/KRT16/DSG1/ANXA2/JUP/LTF/SERPINB3/KRT78/KRT17/CASP14/KRT80/TGM3/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/EEF2/MYH9/SERPINB7/LDHA/UBA52/DMBT1/FLNB/SOD1/HSPB1/ALOX12B/GSTP1/DSC3/C1orf68/CTSV/PGK1/CAPN1/VCL/YWHAE/KRT23/IL1RN/SPRR1B/GSN/IDE/PSMA3/SERPINB5/PNP/KRT15/FLG/PERP/SERPINB13/APOD/CTSB/TYMP/PPIB/ATP5A1/GSS/PSMB3/ACTR2/KRT1/KRT2/KRT10/FLG2/SPRR2E/KRT85 +GO:0007389 pattern specification process 0 0/153 +GO:0007585 respiratory gaseous exchange 0 0/153 +GO:0007586 digestion 5 5/153 SERPINA3/TYMP/AMY1A/AMY1B/AMY1C +GO:0008340 determination of adult lifespan 1 1/153 IDE +GO:0009561 megagametogenesis 0 0/153 +GO:0009791 post-embryonic development 0 0/153 +GO:0009845 seed germination 0 0/153 +GO:0010022 meristem determinacy 0 0/153 +GO:0010073 meristem maintenance 0 0/153 +GO:0010162 seed dormancy process 0 0/153 +GO:0010232 vascular transport 0 0/153 +GO:0016203 muscle attachment 0 0/153 +GO:0019827 stem cell population maintenance 0 0/153 +GO:0022004 midbrain-hindbrain boundary maturation during brain development 0 0/153 +GO:0022005 midbrain-hindbrain boundary maturation during neural plate development 0 0/153 +GO:0022404 molting cycle process 2 2/153 KRT17/TGM3 +GO:0030431 sleep 0 0/153 +GO:0030588 pseudocleavage 0 0/153 +GO:0031424 keratinization 27 27/153 DSP/KRT6A/KRT16/DSG1/JUP/KRT78/KRT17/CASP14/KRT80/TGM3/KRT13/HRNR/KRT6B/SFN/CSTA/DSC3/CAPN1/KRT23/SPRR1B/KRT15/FLG/PERP/KRT1/KRT2/KRT10/SPRR2E/KRT85 +GO:0032898 neurotrophin production 0 0/153 +GO:0032922 circadian regulation of gene expression 0 0/153 +GO:0032941 secretion by tissue 1 1/153 ALOX12B +GO:0033555 multicellular organismal response to stress 0 0/153 +GO:0034381 plasma lipoprotein particle clearance 2 2/153 ANXA2/NPC2 +GO:0035073 pupariation 0 0/153 +GO:0035074 pupation 0 0/153 +GO:0035264 multicellular organism growth 2 2/153 SOD1/PPIB +GO:0035265 organ growth 1 1/153 SOD1 +GO:0035314 scab formation 0 0/153 +GO:0035889 otolith tethering 0 0/153 +GO:0036363 transforming growth factor beta activation 0 0/153 +GO:0042303 molting cycle 3 3/153 KRT16/KRT17/TGM3 +GO:0043480 pigment accumulation in tissues 0 0/153 +GO:0044266 multicellular organismal macromolecule catabolic process 0 0/153 +GO:0044274 multicellular organismal biosynthetic process 0 0/153 +GO:0044706 multi-multicellular organism process 5 5/153 DSG1/ARG1/SOD1/CTSV/CTSB +GO:0045494 photoreceptor cell maintenance 0 0/153 +GO:0048647 polyphenic determination 0 0/153 +GO:0048771 tissue remodeling 3 3/153 ANXA1/ARG1/CAPN1 +GO:0048871 multicellular organismal homeostasis 23 23/153 ALB/KRT16/LTF/ACTG1/PIGR/AZGP1/HRNR/TF/SFN/PRDX1/LYZ/SOD1/HSPB1/ALOX12B/LCN1/SERPINA3/IL1RN/FLG/PIP/ZG16B/CST4/KRT1/FLG2 +GO:0050817 coagulation 10 10/153 ANXA2/ACTG1/MYH9/SERPINA1/HSPB1/YWHAZ/VCL/HBB/CAPZB/KRT1 +GO:0050879 multicellular organismal movement 1 1/153 EEF2 +GO:0051239 regulation of multicellular organismal process 38 38/153 DSP/ANXA2/JUP/LTF/SERPINB3/KRT17/ENO1/LMNA/ANXA1/HSPA5/SFN/ARG1/GAPDH/HSPA1A/HSPA1B/SERPINB7/UBA52/SOD1/HSPB1/EPPK1/ALOX12B/GSTP1/CTSV/PGK1/YWHAE/ORM1/IL1RN/PSMA3/PNP/SERPINB13/APOD/TYMP/PPIB/RPS3/ATP5A1/PSMB3/ACTR2/KRT1 +GO:0051240 positive regulation of multicellular organismal process 20 20/153 ANXA2/LTF/SERPINB3/KRT17/ENO1/ANXA1/HSPA5/GAPDH/HSPA1A/HSPA1B/SERPINB7/SOD1/HSPB1/ALOX12B/ORM1/PNP/PPIB/RPS3/ATP5A1/ACTR2 +GO:0051241 negative regulation of multicellular organismal process 13 13/153 ANXA2/LTF/LMNA/ANXA1/ARG1/UBA52/SOD1/EPPK1/GSTP1/PGK1/ORM1/APOD/KRT1 +GO:0055046 microgametogenesis 0 0/153 +GO:0055127 vibrational conductance of sound to the inner ear 0 0/153 +GO:0060384 innervation 0 0/153 +GO:0071684 organism emergence from protective structure 0 0/153 +GO:0071827 plasma lipoprotein particle organization 1 1/153 ALB +GO:0090130 tissue migration 6 6/153 KRT16/MYH9/HSPB1/EPPK1/ATP5A1/KRT2 +GO:0090664 response to high population density 0 0/153 +GO:0097167 circadian regulation of translation 0 0/153 +GO:0097207 bud dormancy process 0 0/153 +GO:0097242 amyloid-beta clearance 1 1/153 IDE +GO:1990110 callus formation 0 0/153 +GO:0009653 anatomical structure morphogenesis 34 34/153 DSP/KRT16/ANXA2/LTF/ACTG1/KRT17/TGM3/KRT13/ANXA1/HSPA5/S100A7/ARG1/MYH9/POF1B/ACTN4/UBA52/FLNB/SOD1/HSPB1/PGK1/ALDOA/CAPN1/VCL/IL1RN/CST6/PSMA3/SERPINB5/PERP/APOD/TYMP/CAPZB/PSMB3/ACTR2/KRT1 +GO:0007568 aging 11 11/153 KRT16/LMNA/CAT/ARG1/EEF2/SOD1/CTSV/GSN/IDE/APOD/GSS +GO:0007571 age-dependent general metabolic decline 0 0/153 +GO:0009838 abscission 0 0/153 +GO:0009847 spore germination 0 0/153 +GO:0010014 meristem initiation 0 0/153 +GO:0048646 anatomical structure formation involved in morphogenesis 10 10/153 ANXA2/ACTG1/S100A7/MYH9/HSPB1/PGK1/PERP/APOD/TYMP/KRT1 +GO:0021700 developmental maturation 1 1/153 LTF +GO:0022611 dormancy process 0 0/153 +GO:0031128 developmental induction 0 0/153 +GO:0097737 acquisition of mycelium reproductive competence 0 0/153 +GO:0043696 dedifferentiation 0 0/153 +GO:0043934 sporulation 0 0/153 +GO:0044111 development involved in symbiotic interaction 1 1/153 ANXA2 +GO:0048532 anatomical structure arrangement 1 1/153 HSPA5 +GO:0048856 anatomical structure development 82 82/153 DSP/KRT6A/KRT16/DSG1/ANXA2/JUP/LTF/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/KRT80/TGM3/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/EEF2/MYH9/POF1B/SERPINB7/ACTN4/LDHA/UBA52/DMBT1/FLNB/SOD1/HSPB1/EPPK1/ALOX12B/GSTP1/DSC3/C1orf68/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/KRT23/IL1RN/SPRR1B/CST6/GSN/IDE/PSMA3/SERPINB5/PNP/ALDOC/KRT15/FLG/PERP/SERPINB13/APOD/CTSB/TYMP/PPIB/ATP5A1/CAPZB/GSS/PSMB3/ACTR2/CALML5/KRT1/KRT2/KRT10/FLG2/SPRR2E/KRT85 +GO:0050793 regulation of developmental process 28 28/153 ANXA2/LTF/SERPINB3/KRT17/LMNA/ANXA1/HSPA5/SFN/MYH9/SERPINB7/ACTN4/UBA52/SOD1/HSPB1/EPPK1/CTSV/PGK1/ALDOA/IL1RN/PSMA3/PNP/SERPINB13/TYMP/PPIB/CAPZB/PSMB3/ACTR2/KRT1 +GO:0051093 negative regulation of developmental process 5 5/153 ANXA2/LTF/ANXA1/ACTN4/PGK1 +GO:0051094 positive regulation of developmental process 12 12/153 LTF/SERPINB3/KRT17/LMNA/ANXA1/HSPA5/SFN/SERPINB7/HSPB1/PNP/PPIB/ACTR2 +GO:0060033 anatomical structure regression 0 0/153 +GO:0090644 age-related resistance 0 0/153 +GO:0098727 maintenance of cell number 0 0/153 +GO:0031987 locomotion involved in locomotory behavior 0 0/153 +GO:0033058 directional locomotion 0 0/153 +GO:0036268 swimming 0 0/153 +GO:0040012 regulation of locomotion 14 14/153 KRT16/SERPINB3/LMNA/ANXA1/HSPA5/S100A7/ACTN4/HSPB1/EPPK1/GSTP1/VCL/S100A14/APOD/ATP5A1 +GO:0040013 negative regulation of locomotion 5 5/153 KRT16/EPPK1/GSTP1/VCL/APOD +GO:0040017 positive regulation of locomotion 7 7/153 SERPINB3/HSPA5/S100A7/ACTN4/HSPB1/S100A14/ATP5A1 +GO:0042330 taxis 6 6/153 ANXA1/S100A7/HSPB1/GSTP1/S100A14/TYMP +GO:0048870 cell motility 19 19/153 KRT16/JUP/SERPINB3/LMNA/ANXA1/HSPA5/S100A7/MYH9/ACTN4/HSPB1/EPPK1/PPIA/GSTP1/VCL/YWHAE/S100A14/APOD/ATP5A1/KRT2 +GO:0051821 dissemination or transmission of organism from other organism involved in symbiotic interaction 0 0/153 +GO:0052192 movement in environment of other organism involved in symbiotic interaction 1 1/153 PPIA +GO:0060361 flight 0 0/153 +GO:0071965 multicellular organismal locomotion 0 0/153 +GO:0033060 ocellus pigmentation 0 0/153 +GO:0043474 pigment metabolic process involved in pigmentation 0 0/153 +GO:0043476 pigment accumulation 0 0/153 +GO:0048066 developmental pigmentation 0 0/153 +GO:0022403 cell cycle phase 0 0/153 +GO:0022601 menstrual cycle phase 0 0/153 +GO:0044851 hair cycle phase 0 0/153 +GO:0060206 estrous cycle phase 0 0/153 +GO:0072690 single-celled organism vegetative growth phase 0 0/153 +GO:0007623 circadian rhythm 0 0/153 +GO:0007624 ultradian rhythm 0 0/153 +GO:0042698 ovulation cycle 2 2/153 ANXA1/SOD1 +GO:0032846 positive regulation of homeostatic process 1 1/153 ANXA1 +GO:0042753 positive regulation of circadian rhythm 0 0/153 +GO:0043902 positive regulation of multi-organism process 5 5/153 ARG1/GAPDH/HSPA8/PPIA/PPIB +GO:0044089 positive regulation of cellular component biogenesis 7 7/153 HSPA1A/HSPA1B/GSN/IDE/RPS3/ARPC4/ACTR2 +GO:0045760 positive regulation of action potential 0 0/153 +GO:0045785 positive regulation of cell adhesion 3 3/153 ANXA1/PNP/RPS3 +GO:0048087 positive regulation of developmental pigmentation 0 0/153 +GO:0048584 positive regulation of response to stimulus 33 33/153 JUP/LTF/MUC5B/ACTG1/ANXA1/CAT/S100A7/SFN/ARG1/HSPA1A/HSPA1B/HSP90AA1/ACTN4/UBA52/TXN/DMBT1/SOD1/HSPB1/YWHAZ/ALOX12B/YWHAE/S100A14/GSN/PSMA3/CTSB/LAMP1/RPS3/PSMB3/ARPC4/ACTR2/MUC7/KRT1/SERPINA12 +GO:0051050 positive regulation of transport 13 13/153 ANXA2/JUP/ANXA1/TF/SFN/GAPDH/ACTN4/PPIA/YWHAZ/ALOX12B/YWHAE/ORM1/LAMP1 +GO:0051091 positive regulation of DNA binding transcription factor activity 7 7/153 JUP/LTF/CAT/HSPA1A/HSPA1B/UBA52/RPS3 +GO:0051919 positive regulation of fibrinolysis 0 0/153 +GO:0060301 positive regulation of cytokine activity 0 0/153 +GO:1900048 positive regulation of hemostasis 0 0/153 +GO:1900097 positive regulation of dosage compensation by inactivation of X chromosome 0 0/153 +GO:1900454 positive regulation of long term synaptic depression 0 0/153 +GO:1902474 positive regulation of protein localization to synapse 0 0/153 +GO:1902632 positive regulation of membrane hyperpolarization 0 0/153 +GO:1902685 positive regulation of receptor localization to synapse 0 0/153 +GO:1903549 positive regulation of growth hormone activity 0 0/153 +GO:1903666 positive regulation of asexual reproduction 0 0/153 +GO:1903829 positive regulation of cellular protein localization 4 4/153 JUP/SFN/YWHAZ/YWHAE +GO:1904181 positive regulation of membrane depolarization 0 0/153 +GO:1904582 positive regulation of intracellular mRNA localization 0 0/153 +GO:1904704 positive regulation of protein localization to cell-cell adherens junction 0 0/153 +GO:1904874 positive regulation of telomerase RNA localization to Cajal body 0 0/153 +GO:1904912 positive regulation of establishment of RNA localization to telomere 0 0/153 +GO:1904915 positive regulation of establishment of macromolecular complex localization to telomere 0 0/153 +GO:1904951 positive regulation of establishment of protein localization 7 7/153 JUP/SFN/GAPDH/PPIA/YWHAZ/YWHAE/ORM1 +GO:1905099 positive regulation of guanyl-nucleotide exchange factor activity 0 0/153 +GO:1905339 positive regulation of cohesin unloading 0 0/153 +GO:1905514 positive regulation of short-term synaptic potentiation 0 0/153 +GO:1905605 positive regulation of maintenance of permeability of blood-brain barrier 0 0/153 +GO:1905954 positive regulation of lipid localization 1 1/153 ANXA2 +GO:2000199 positive regulation of ribonucleoprotein complex localization 0 0/153 +GO:2000327 positive regulation of ligand-dependent nuclear receptor transcription coactivator activity 0 0/153 +GO:0008588 release of cytoplasmic sequestered NF-kappaB 0 0/153 +GO:0034260 negative regulation of GTPase activity 0 0/153 +GO:0032845 negative regulation of homeostatic process 0 0/153 +GO:0042754 negative regulation of circadian rhythm 0 0/153 +GO:0043433 negative regulation of DNA binding transcription factor activity 1 1/153 CAT +GO:0043901 negative regulation of multi-organism process 3 3/153 ANXA2/LTF/GSN +GO:0045759 negative regulation of action potential 0 0/153 +GO:0048086 negative regulation of developmental pigmentation 0 0/153 +GO:0048585 negative regulation of response to stimulus 22 22/153 ANXA2/LTF/SERPINB3/ENO1/LMNA/ANXA1/HSPA5/ARG1/HSPA1A/HSPA1B/UBA52/TXN/HSPB1/EPPK1/GSTP1/SERPINB4/IL1RN/PSMA3/APOD/RPS3/PSMB3/KRT1 +GO:0051051 negative regulation of transport 5 5/153 ANXA1/HSPA1A/TXN/YWHAE/APOD +GO:0051918 negative regulation of fibrinolysis 0 0/153 +GO:0060302 negative regulation of cytokine activity 0 0/153 +GO:1900047 negative regulation of hemostasis 2 2/153 ANXA2/KRT1 +GO:1900096 negative regulation of dosage compensation by inactivation of X chromosome 0 0/153 +GO:1900272 negative regulation of long-term synaptic potentiation 0 0/153 +GO:1900453 negative regulation of long term synaptic depression 0 0/153 +GO:1902631 negative regulation of membrane hyperpolarization 0 0/153 +GO:1902684 negative regulation of receptor localization to synapse 0 0/153 +GO:1902886 negative regulation of proteasome-activating ATPase activity 0 0/153 +GO:1903548 negative regulation of growth hormone activity 0 0/153 +GO:1903665 negative regulation of asexual reproduction 0 0/153 +GO:1903828 negative regulation of cellular protein localization 2 2/153 TXN/APOD +GO:1904180 negative regulation of membrane depolarization 0 0/153 +GO:1904537 negative regulation of mitotic telomere tethering at nuclear periphery 0 0/153 +GO:1904581 negative regulation of intracellular mRNA localization 0 0/153 +GO:1904703 negative regulation of protein localization to cell-cell adherens junction 0 0/153 +GO:1904873 negative regulation of telomerase RNA localization to Cajal body 0 0/153 +GO:1904911 negative regulation of establishment of RNA localization to telomere 0 0/153 +GO:1904914 negative regulation of establishment of macromolecular complex localization to telomere 0 0/153 +GO:1904950 negative regulation of establishment of protein localization 3 3/153 ANXA1/TXN/APOD +GO:1905098 negative regulation of guanyl-nucleotide exchange factor activity 0 0/153 +GO:1905338 negative regulation of cohesin unloading 0 0/153 +GO:1905385 negative regulation of protein localization to presynapse 0 0/153 +GO:1905513 negative regulation of short-term synaptic potentiation 0 0/153 +GO:1905604 negative regulation of maintenance of permeability of blood-brain barrier 0 0/153 +GO:1905869 negative regulation of 3'-UTR-mediated mRNA stabilization 0 0/153 +GO:1905953 negative regulation of lipid localization 0 0/153 +GO:2000198 negative regulation of ribonucleoprotein complex localization 0 0/153 +GO:2000326 negative regulation of ligand-dependent nuclear receptor transcription coactivator activity 0 0/153 +GO:0030155 regulation of cell adhesion 9 9/153 ANXA1/ARG1/ACTN4/SOD1/IL1RN/GSN/PNP/APOD/RPS3 +GO:0032844 regulation of homeostatic process 1 1/153 ANXA1 +GO:0032879 regulation of localization 32 32/153 DSP/KRT16/ANXA2/JUP/SERPINB3/LMNA/ANXA1/HSPA5/TF/S100A7/SFN/PRDX1/ARG1/GAPDH/HSPA1A/ACTN4/TXN/HSPB1/HSPA8/EPPK1/PPIA/YWHAZ/ALOX12B/GSTP1/VCL/YWHAE/ORM1/S100A14/GSN/APOD/LAMP1/ATP5A1 +GO:0042752 regulation of circadian rhythm 0 0/153 +GO:0043900 regulation of multi-organism process 8 8/153 ANXA2/LTF/ARG1/GAPDH/HSPA8/PPIA/GSN/PPIB +GO:0044087 regulation of cellular component biogenesis 12 12/153 HSPA1A/HSPA1B/HSP90AA1/HSPA8/GSN/IDE/APOD/RPS3/CAPG/CAPZB/ARPC4/ACTR2 +GO:0048070 regulation of developmental pigmentation 0 0/153 +GO:0048518 positive regulation of biological process 59 59/153 ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT17/ENO1/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/SERPINB7/HSP90AA1/ACTN4/LDHA/UBA52/TXN/DMBT1/SOD1/HSPB1/HSPA8/PPIA/YWHAZ/ALOX12B/GSTP1/CAPN1/YWHAE/HBB/HP/ORM1/LCN2/S100A14/GSN/IDE/PSMA3/PNP/PERP/CTSB/LAMP1/PPIB/RPS3/ATP5A1/PSMB3/ARPC4/ACTR2/PIP/MUC7/KRT1/SERPINA12 +GO:0048519 negative regulation of biological process 63 63/153 ALB/KRT16/ANXA2/LTF/SERPINB3/ENO1/AZGP1/LMNA/ANXA1/HSPA5/CAT/SFN/SERPINB12/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/MYH9/SERPINB7/SERPINA1/ACTN4/UBA52/TXN/SOD1/HSPB1/HSPA8/EPPK1/EIF4A1/YWHAZ/GSTP1/LCN1/SERPINB4/PGK1/VCL/YWHAE/A2ML1/HP/SERPINA3/ORM1/IL1RN/SERPINB1/CST6/GSN/IDE/PSMA3/SERPINB5/CSTB/SERPINB13/APOD/RPSA/RPS3/ATP5A1/S100A11/CAPG/CAPZB/PSMB3/PIP/CST4/CST1/CST2/KRT1/SERPINA12 +GO:0048583 regulation of response to stimulus 49 49/153 ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/PIGR/ENO1/LMNA/ANXA1/HSPA5/CAT/S100A7/SFN/PRDX1/ARG1/HSPA1A/HSPA1B/HSP90AA1/IL36G/ACTN4/UBA52/TXN/DMBT1/SOD1/HSPB1/HSPA8/EPPK1/YWHAZ/ALOX12B/GSTP1/SERPINB4/YWHAE/IL1RN/S100A14/GSN/PSMA3/APOD/CTSB/LAMP1/TYMP/RPS3/PSMB3/GDI2/ARPC4/ACTR2/MUC7/KRT1/SERPINA12 +GO:0071898 regulation of estrogen receptor binding 0 0/153 +GO:0097006 regulation of plasma lipoprotein particle levels 3 3/153 ALB/ANXA2/NPC2 +GO:0098900 regulation of action potential 2 2/153 DSP/JUP +GO:1900046 regulation of hemostasis 2 2/153 ANXA2/KRT1 +GO:1902630 regulation of membrane hyperpolarization 0 0/153 +GO:1903664 regulation of asexual reproduction 0 0/153 +GO:1905097 regulation of guanyl-nucleotide exchange factor activity 0 0/153 +GO:1905603 regulation of maintenance of permeability of blood-brain barrier 0 0/153 +GO:0006950 response to stress 66 66/153 DSP/ALB/KRT16/ANXA2/LTF/MUC5B/SERPINB3/ACTG1/ENO1/LMNA/ANXA1/HSPA5/CAT/S100A7/SFN/PKM/PRDX1/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/LYZ/SERPINA1/HSP90AA1/IL36G/ACTN4/LDHA/UBA52/TXN/DMBT1/SOD1/HSPB1/HSPA8/EPPK1/YWHAZ/GSTP1/SERPINB4/CTSV/PGK1/VCL/YWHAE/HBB/HP/SERPINA3/ORM1/IL1RN/LCN2/S100A14/GSN/PSMA3/APOD/CTSB/LAMP1/LAMP2/RPS3/CAPZB/GSS/PSMB3/ACTR2/MUC7/KRT1/DCD/DEFA3 +GO:0009605 response to external stimulus 36 36/153 ALB/ANXA2/JUP/LTF/ENO1/ANXA1/HSPA5/CAT/S100A7/PKM/ARG1/GAPDH/EEF2/LYZ/LDHA/DMBT1/SOD1/HSPB1/HSPA8/EPPK1/GSTP1/CTSV/HP/LCN2/S100A14/GSN/EEF1G/APOD/LAMP2/TYMP/GSS/NPC2/MUC7/KRT1/DCD/DEFA3 +GO:0009607 response to biotic stimulus 18 18/153 LTF/ENO1/HSPA5/S100A7/ARG1/GAPDH/LYZ/DMBT1/HSPB1/GSTP1/HP/LCN2/S100A14/EEF1G/NPC2/MUC7/DCD/DEFA3 +GO:0009628 response to abiotic stimulus 22 22/153 JUP/ENO1/KRT13/LMNA/ANXA1/HSPA5/CAT/PKM/HSPA1A/HSPA1B/HSP90AA1/ACTN4/LDHA/UBA52/TXN/SOD1/HSPA8/PGK1/YWHAE/PSMA3/SERPINB13/PSMB3 +GO:0009719 response to endogenous stimulus 21 21/153 DSG1/ANXA2/JUP/ANXA1/HSPA5/CAT/PKM/ARG1/HSPA1A/EEF2/UBA52/SOD1/GGH/GSTP1/CTSV/IL1RN/IDE/CTSB/ACTR2/SERPINA12/DEFA3 +GO:0014823 response to activity 1 1/153 CAT +GO:0014854 response to inactivity 2 2/153 CAT/PKM +GO:0014874 response to stimulus involved in regulation of muscle adaptation 0 0/153 +GO:0042221 response to chemical 59 59/153 ALB/DSG1/ANXA2/JUP/LTF/PIGR/ENO1/AZGP1/KRT13/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/PKM/PRDX1/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/TUBA1B/HSP90AA1/IL36G/LDHA/UBA52/TXN/BLMH/SOD1/HSPB1/HSPA8/PPIA/GGH/GSTP1/CTSV/PGK1/HBB/HP/IL1RN/LCN2/S100A14/GSN/IDE/PSMA3/PNP/APOD/CTSB/TYMP/RPS3/GSS/PSMB3/ACTR2/PIP/CST4/CST1/CST2/SERPINA12/DEFA3 +GO:0043500 muscle adaptation 2 2/153 LMNA/GSN +GO:0043627 response to estrogen 1 1/153 LDHA +GO:0051606 detection of stimulus 9 9/153 JUP/PIGR/AZGP1/UBA52/RPS3/PIP/CST4/CST1/CST2 +GO:0051775 response to redox state 0 0/153 +GO:0072376 protein activation cascade 1 1/153 KRT1 +GO:0032187 actomyosin contractile ring localization 0 0/153 +GO:0033036 macromolecule localization 38 38/153 DSP/ALB/ANXA2/JUP/PIGR/AZGP1/LMNA/ANXA1/HSPA5/TF/SFN/PRDX1/GAPDH/MYH9/HSP90AA1/ACTN4/UBA52/TXN/DMBT1/FLNB/HSPB1/HSPA8/PPIA/YWHAZ/LCN1/VCL/YWHAE/ORM1/IL1RN/GSN/PNP/APOD/RPSA/LAMP1/LAMP2/RPS3/GDI2/NPC2 +GO:0035732 nitric oxide storage 1 1/153 GSTP1 +GO:0051234 establishment of localization 82 82/153 DSP/ALB/DSG1/ANXA2/JUP/LTF/SERPINB3/ACTG1/FABP5/PIGR/AZGP1/HRNR/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/PRDX1/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/CTSD/UBA52/TXN/DMBT1/SOD1/HSPB1/HSPA8/PPIA/YWHAZ/GGH/ALOX12B/GSTP1/LCN1/ALDOA/CAPN1/VCL/YWHAE/HBB/HP/SERPINA3/ORM1/IL1RN/SERPINB1/LCN2/GSN/AGA/PSMA3/PNP/CSTB/ALDOC/APOD/CTSB/RPSA/LAMP1/LAMP2/RPS3/ATP5A1/S100A11/CAPZB/PSMB3/GDI2/ARPC4/ACTR2/NPC2/CALML5/PIP/KRT1/FLG2 +GO:0051235 maintenance of location 6 6/153 ALB/JUP/HSPA5/S100A7/FLNB/GSN +GO:0051641 cellular localization 34 34/153 ALB/ANXA2/JUP/PIGR/LMNA/HSPA5/SFN/PRDX1/HSPA1A/MYH9/TUBB4B/TUBA1B/SERPINA1/HSP90AA1/ACTN4/UBA52/TXN/FLNB/SOD1/HSPB1/HSPA8/YWHAZ/VCL/YWHAE/GSN/APOD/RPSA/LAMP1/LAMP2/RPS3/ATP5A1/CAPZB/ACTR2/NPC2 +GO:0051674 localization of cell 19 19/153 KRT16/JUP/SERPINB3/LMNA/ANXA1/HSPA5/S100A7/MYH9/ACTN4/HSPB1/EPPK1/PPIA/GSTP1/VCL/YWHAE/S100A14/APOD/ATP5A1/KRT2 +GO:0061842 microtubule organizing center localization 0 0/153 +GO:1902579 multi-organism localization 1 1/153 UBA52 +GO:0051707 response to other organism 17 17/153 LTF/ENO1/S100A7/ARG1/GAPDH/LYZ/DMBT1/HSPB1/GSTP1/HP/LCN2/S100A14/EEF1G/NPC2/MUC7/DCD/DEFA3 +GO:0044366 feeding on or from other organism 0 0/153 +GO:0044419 interspecies interaction between organisms 27 27/153 ALB/ANXA2/LTF/SERPINB3/ARG1/GAPDH/HSPA1A/HSPA1B/LYZ/UBA52/DMBT1/HSPA8/EIF4A1/PPIA/YWHAE/GSN/IDE/PSMA3/CTSB/RPSA/LAMP1/PPIB/RPS3/PSMB3/MUC7/DCD/DEFA3 +GO:0051703 intraspecies interaction between organisms 0 0/153 +GO:0051816 acquisition of nutrients from other organism during symbiotic interaction 0 0/153 +GO:0098630 aggregation of unicellular organisms 0 0/153 +GO:0098740 multi organism cell adhesion 0 0/153 +GO:0050789 regulation of biological process 101 101/153 DSP/ALB/KRT16/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT17/PIGR/ENO1/AZGP1/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/SERPINB7/SERPINA1/HSP90AA1/IL36G/ACTN4/GGCT/LDHA/UBA52/TXN/DMBT1/FLNB/SOD1/HSPB1/HSPA8/EPPK1/EIF4A1/PPIA/YWHAZ/ALOX12B/GSTP1/LCN1/SERPINB4/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/HBB/A2ML1/HP/SERPINA3/ORM1/IL1RN/SERPINB1/LCN2/CST6/S100A14/GSN/IDE/PSMA3/SERPINB5/PNP/CSTB/PERP/SERPINB13/APOD/CTSB/RPSA/LAMP1/TYMP/PPIB/RPS3/ATP5A1/S100A11/CAPG/CAPZB/PSMB3/GDI2/ARPC4/ACTR2/NPC2/CALML5/PIP/CST4/MUC7/CST1/CST2/KRT1/SERPINA12/DEFA3 +GO:0065008 regulation of biological quality 60 60/153 DSP/ALB/KRT16/DSG1/ANXA2/JUP/LTF/ACTG1/PIGR/AZGP1/HRNR/ANXA1/HSPA5/TF/S100A7/SFN/PRDX1/GAPDH/HSPA1A/HSPA1B/MYH9/LYZ/SERPINA1/HSP90AA1/UBA52/TXN/FLNB/SOD1/HSPB1/HSPA8/YWHAZ/ALOX12B/GSTP1/LCN1/ALDOA/VCL/YWHAE/HBB/SERPINA3/IL1RN/LCN2/S100A14/GSN/IDE/PSMA3/FLG/LAMP1/LAMP2/PPIB/CAPG/CAPZB/PSMB3/ARPC4/ACTR2/NPC2/PIP/ZG16B/CST4/KRT1/FLG2 +GO:0065009 regulation of molecular function 48 48/153 ANXA2/JUP/LTF/SERPINB3/ANXA1/HSPA5/CAT/SFN/SERPINB12/CSTA/GAPDH/HSPA1A/HSPA1B/SERPINB7/SERPINA1/HSP90AA1/IL36G/ACTN4/UBA52/TXN/SOD1/HSPB1/GSTP1/LCN1/SERPINB4/CAPN1/YWHAE/A2ML1/HP/SERPINA3/IL1RN/SERPINB1/CST6/GSN/PSMA3/SERPINB5/CSTB/PERP/SERPINB13/CTSB/TYMP/RPS3/PSMB3/GDI2/CST4/CST1/CST2/SERPINA12 +GO:1902727 negative regulation of growth factor dependent skeletal muscle satellite cell proliferation 0 0/153 +GO:1902728 positive regulation of growth factor dependent skeletal muscle satellite cell proliferation 0 0/153 +GO:0044085 cellular component biogenesis 33 33/153 DSG1/ANXA2/JUP/ACTG1/PLEC/TGM3/CAT/PKM/ARG1/HSPA1A/HSPA1B/TUBB4B/POF1B/SERPINA1/HSP90AA1/ACTN4/UBA52/HSPA8/YWHAZ/ALDOA/VCL/YWHAE/HBB/LCN2/GSN/IDE/APOD/RPSA/RPS3/CAPG/CAPZB/ARPC4/ACTR2 +GO:0001502 cartilage condensation 0 0/153 +GO:0009407 toxin catabolic process 0 0/153 +GO:0010127 mycothiol-dependent detoxification 0 0/153 +GO:0010312 detoxification of zinc ion 0 0/153 +GO:0051410 detoxification of nitrogen compound 0 0/153 +GO:0061687 detoxification of inorganic compound 0 0/153 +GO:0071722 detoxification of arsenic-containing substance 0 0/153 +GO:1990748 cellular detoxification 8 8/153 ALB/CAT/PRDX1/TXN/SOD1/GSTP1/HBB/HP +GO:0016080 synaptic vesicle targeting 0 0/153 +GO:0007269 neurotransmitter secretion 1 1/153 HSPA8 +GO:0016079 synaptic vesicle exocytosis 0 0/153 +GO:0016081 synaptic vesicle docking 0 0/153 +GO:0016082 synaptic vesicle priming 0 0/153 +GO:0031629 synaptic vesicle fusion to presynaptic active zone membrane 0 0/153 +GO:0051583 dopamine uptake involved in synaptic transmission 0 0/153 +GO:0099069 synaptic vesicle tethering involved in synaptic vesicle exocytosis 0 0/153 +GO:0099502 calcium-dependent activation of synaptic vesicle fusion 0 0/153 +GO:0099703 induction of synaptic vesicle exocytosis by positive regulation of presynaptic cytosolic calcium ion concentration 0 0/153
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/cluster_profiler_GGO_CC.csv Tue Dec 18 09:21:32 2018 -0500 @@ -0,0 +1,381 @@ +ID Description Count GeneRatio geneID +GO:0005886 plasma membrane 56 56/153 DSP/DSG1/ANXA2/JUP/MUC5B/ACTG1/FABP5/PIGR/ENO1/AZGP1/PLEC/TGM3/HRNR/ANXA1/HSPA5/TF/CAT/SERPINB12/CSTA/GAPDH/EEF2/MYH9/HSP90AA1/UBA52/FLNB/SOD1/HSPB1/HSPA8/EPPK1/GSTP1/DSC3/C1orf68/CTSV/CAPN1/VCL/YWHAE/IL1RN/SPRR1B/CST6/GSN/IDE/LYPD3/FLG/PERP/RPSA/LAMP1/LAMP2/RPS3/ATP5A1/PIP/MUC7/KRT1/KRT2/KRT10/SERPINA12/SPRR2E +GO:0005628 prospore membrane 0 0/153 +GO:0005789 endoplasmic reticulum membrane 2 2/153 HSPA5/UBA52 +GO:0019867 outer membrane 2 2/153 ARG1/UBA52 +GO:0031090 organelle membrane 24 24/153 DSP/DSG1/ANXA2/FABP5/PIGR/LMNA/ANXA1/TF/CAT/SFN/SERPINB12/ARG1/GAPDH/SERPINA1/UBA52/DMBT1/HSPA8/YWHAZ/YWHAE/MDH2/LAMP1/LAMP2/RPS3/ATP5A1 +GO:0034357 photosynthetic membrane 0 0/153 +GO:0036362 ascus membrane 0 0/153 +GO:0042175 nuclear outer membrane-endoplasmic reticulum membrane network 2 2/153 HSPA5/UBA52 +GO:0044425 membrane part 29 29/153 DSP/DSG1/ANXA2/JUP/PIGR/TGM3/ANXA1/HSPA5/TF/EEF2/MYH9/TUBA1B/HSP90AA1/CTSD/UBA52/DMBT1/FLNB/HSPA8/EPPK1/DSC3/CTSV/PGK1/LYPD3/PERP/LAMP1/LAMP2/RPS3/ATP5A1/PIP +GO:0048475 coated membrane 0 0/153 +GO:0055036 virion membrane 0 0/153 +GO:0098589 membrane region 7 7/153 ANXA2/TF/EEF2/TUBA1B/CTSD/PGK1/LAMP2 +GO:0098590 plasma membrane region 10 10/153 DSP/DSG1/ANXA2/JUP/ANXA1/TF/HSP90AA1/EPPK1/RPS3/PIP +GO:0098805 whole membrane 19 19/153 DSP/DSG1/ANXA2/FABP5/PIGR/ANXA1/TF/CAT/SERPINB12/ARG1/EEF2/TUBA1B/CTSD/UBA52/DMBT1/HSPA8/PGK1/LAMP1/LAMP2 +GO:1990578 perinuclear endoplasmic reticulum membrane 0 0/153 +GO:0043083 synaptic cleft 0 0/153 +GO:0044421 extracellular region part 141 141/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/AZGP1/PLEC/TGM3/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/SERPINB7/LYZ/TUBA1B/SERPINA1/HSP90AA1/IL36G/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/CPA4/LGALS7B/BLMH/PLBD1/FLNB/SOD1/HSPB1/HSPA8/EIF4A1/PPIA/YWHAZ/GGH/GSTP1/LCN1/SERPINB4/C1orf68/SBSN/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/HBB/A2ML1/HP/SERPINA3/ORM1/IL1RN/SPRR1B/SERPINB1/LCN2/CST6/S100A14/GSN/IDE/AGA/PSMA3/EEF1G/SERPINB5/MDH2/FCGBP/LYPD3/PNP/CSTB/ALDOC/KRT15/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP1/LAMP2/PPIB/RPS3/ATP5A1/CALML3/S100A11/CAPG/CAPZB/GSS/PSMB3/GDI2/ARPC4/ACTR2/NPC2/AMY1A/AMY1B/AMY1C/CALML5/PIP/ZG16B/CST4/MUC7/CST1/CST2/KRT1/KRT2/KRT10/FLG2/KPRP/SERPINA12/DCD/DEFA3/KRT85 +GO:0048046 apoplast 0 0/153 +GO:0098595 perivitelline space 0 0/153 +GO:0099544 perisynaptic space 0 0/153 +GO:0044464 cell part 137 137/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/AZGP1/PLEC/KRT80/TGM3/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/POF1B/SERPINB7/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/LGALS7B/BLMH/PLBD1/FLNB/SOD1/HSPB1/HSPA8/EPPK1/EIF4A1/PPIA/YWHAZ/GGH/ALOX12B/GSTP1/SERPINB4/DSC3/C1orf68/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/HBB/KRT23/HP/SERPINA3/ORM1/IL1RN/SPRR1B/SERPINB1/LCN2/CST6/S100A14/GSN/IDE/AGA/PSMA3/EEF1G/SERPINB5/MDH2/LYPD3/PNP/CSTB/ALDOC/KRT15/FLG/PERP/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP1/LAMP2/TYMP/PPIB/RPS3/ATP5A1/S100A11/CAPG/HAL/CAPZB/GSS/PSMB3/GDI2/ARPC4/ACTR2/NPC2/CALML5/PIP/MUC7/KRT1/KRT2/KRT10/FLG2/KPRP/SERPINA12/SPRR2E/DEFA3/KRT85 +GO:0039642 virion nucleoid 0 0/153 +GO:0042645 mitochondrial nucleoid 0 0/153 +GO:0042646 plastid nucleoid 0 0/153 +GO:0043590 bacterial nucleoid 0 0/153 +GO:0044777 single-stranded DNA-binding protein complex 0 0/153 +GO:0044423 virion part 0 0/153 +GO:0005911 cell-cell junction 13 13/153 DSP/DSG1/ANXA2/JUP/ANXA1/MYH9/POF1B/ACTN4/EPPK1/DSC3/VCL/PERP/S100A11 +GO:0030055 cell-substrate junction 25 25/153 JUP/ACTG1/PLEC/ANXA1/HSPA5/CAT/S100A7/HSPA1A/HSPA1B/MYH9/ACTN4/FLNB/HSPB1/HSPA8/EPPK1/PPIA/YWHAZ/CAPN1/VCL/YWHAE/GSN/PPIB/RPS3/GDI2/ACTR2 +GO:0061466 plasma membrane part of cell junction 0 0/153 +GO:0070161 anchoring junction 31 31/153 DSP/DSG1/ANXA2/JUP/ACTG1/PLEC/ANXA1/HSPA5/CAT/S100A7/HSPA1A/HSPA1B/MYH9/POF1B/ACTN4/FLNB/HSPB1/HSPA8/PPIA/YWHAZ/DSC3/CAPN1/VCL/YWHAE/GSN/PERP/PPIB/RPS3/S100A11/GDI2/ACTR2 +GO:0043233 organelle lumen 70 70/153 ALB/ANXA2/JUP/LTF/MUC5B/SERPINB3/FABP5/HRNR/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/PKM/ARG1/HSPA1A/HSPA1B/EEF2/TUBB4B/LYZ/SERPINA1/HSP90AA1/ACTN4/CTSD/UBA52/SOD1/HSPA8/EPPK1/PPIA/YWHAZ/GGH/GSTP1/CTSV/ALDOA/CAPN1/VCL/HBB/HP/SERPINA3/ORM1/SERPINB1/LCN2/S100A14/GSN/IDE/AGA/PSMA3/MDH2/PNP/CSTB/ALDOC/SERPINB13/CTSB/RPSA/LAMP2/PPIB/RPS3/ATP5A1/S100A11/CAPG/PSMB3/GDI2/ACTR2/NPC2/CALML5/MUC7/KRT1/FLG2/DEFA3 +GO:0001114 protein-DNA-RNA complex 0 0/153 +GO:0005952 cAMP-dependent protein kinase complex 0 0/153 +GO:0016533 cyclin-dependent protein kinase 5 holoenzyme complex 0 0/153 +GO:0017053 transcriptional repressor complex 0 0/153 +GO:0032992 protein-carbohydrate complex 0 0/153 +GO:0032993 protein-DNA complex 1 1/153 JUP +GO:0032994 protein-lipid complex 0 0/153 +GO:0034518 RNA cap binding complex 0 0/153 +GO:0035003 subapical complex 0 0/153 +GO:0036125 fatty acid beta-oxidation multienzyme complex 0 0/153 +GO:0043234 protein complex 33 33/153 ALB/ANXA2/JUP/LTF/ACTG1/ANXA1/HSPA5/GAPDH/HSPA1A/HSPA1B/MYH9/HSP90AA1/ACTN4/SOD1/HSPB1/HSPA8/EIF4A1/GSTP1/VCL/YWHAE/HBB/HP/GSN/IDE/PSMA3/PPIB/RPS3/ATP5A1/CAPG/CAPZB/PSMB3/ARPC4/ACTR2 +GO:0043235 receptor complex 3 3/153 PIGR/TF/MYH9 +GO:0044815 DNA packaging complex 0 0/153 +GO:0046536 dosage compensation complex 0 0/153 +GO:0061742 chaperone-mediated autophagy translocation complex 0 0/153 +GO:0061838 CENP-T-W-S-X complex 0 0/153 +GO:0061927 TOC-TIC supercomplex I 0 0/153 +GO:0070864 sperm individualization complex 0 0/153 +GO:0098636 protein complex involved in cell adhesion 1 1/153 MYH9 +GO:0098774 curli 0 0/153 +GO:0099023 tethering complex 0 0/153 +GO:0140007 KICSTOR complex 0 0/153 +GO:1902494 catalytic complex 9 9/153 ENO1/PKM/HSPA1A/HSPA1B/HSPB1/HSPA8/IDE/PSMA3/PSMB3 +GO:1902695 metallochaperone complex 0 0/153 +GO:1902773 GTPase activator complex 0 0/153 +GO:1903269 ornithine carbamoyltransferase inhibitor complex 0 0/153 +GO:1903502 translation repressor complex 0 0/153 +GO:1903503 ATPase inhibitor complex 0 0/153 +GO:1903865 sigma factor antagonist complex 0 0/153 +GO:1904090 peptidase inhibitor complex 0 0/153 +GO:1990104 DNA bending complex 0 0/153 +GO:1990229 iron-sulfur cluster assembly complex 0 0/153 +GO:1990249 nucleotide-excision repair, DNA damage recognition complex 0 0/153 +GO:1990351 transporter complex 0 0/153 +GO:1990391 DNA repair complex 0 0/153 +GO:1990415 Pex17p-Pex14p docking complex 0 0/153 +GO:1990684 protein-lipid-RNA complex 0 0/153 +GO:1990862 nuclear membrane complex Bqt3-Bqt4 0 0/153 +GO:1990904 ribonucleoprotein complex 10 10/153 GAPDH/HSPA1A/HSPA1B/EEF2/ACTN4/UBA52/HSPA8/APOD/RPSA/RPS3 +GO:1990923 PET complex 0 0/153 +GO:0005929 cilium 2 2/153 ANXA1/PKM +GO:0043227 membrane-bounded organelle 136 136/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/AZGP1/PLEC/TGM3/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/LGALS7B/BLMH/PLBD1/FLNB/SOD1/HSPB1/HSPA8/EPPK1/EIF4A1/PPIA/YWHAZ/GGH/GSTP1/LCN1/SERPINB4/C1orf68/SBSN/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/HBB/A2ML1/HP/SERPINA3/ORM1/IL1RN/SPRR1B/SERPINB1/LCN2/CST6/S100A14/GSN/IDE/AGA/PSMA3/EEF1G/SERPINB5/MDH2/FCGBP/PNP/CSTB/ALDOC/KRT15/FLG/PERP/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP1/LAMP2/PPIB/RPS3/ATP5A1/CALML3/S100A11/CAPG/CAPZB/GSS/PSMB3/GDI2/ARPC4/ACTR2/NPC2/AMY1A/AMY1B/AMY1C/CALML5/PIP/ZG16B/CST4/MUC7/KRT1/KRT2/KRT10/FLG2/KPRP/DCD/DEFA3 +GO:0043228 non-membrane-bounded organelle 51 51/153 DSP/KRT6A/KRT16/ANXA2/JUP/ACTG1/KRT78/KRT17/CASP14/ENO1/PLEC/KRT80/KRT13/KRT6B/LMNA/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/POF1B/TUBA1B/ACTN4/UBA52/FLNB/HSPB1/HSPA8/EPPK1/ALDOA/VCL/YWHAE/KRT23/GSN/PNP/CSTB/ALDOC/KRT15/FLG/APOD/CTSB/RPSA/RPS3/CAPG/CAPZB/ARPC4/ACTR2/KRT1/KRT2/KRT10/KRT85 +GO:0043229 intracellular organelle 116 116/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/AZGP1/PLEC/KRT80/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/POF1B/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/LDHA/CTSD/UBA52/TXN/DMBT1/LGALS7B/BLMH/PLBD1/FLNB/SOD1/HSPB1/HSPA8/EPPK1/PPIA/YWHAZ/GGH/GSTP1/CTSV/ALDOA/CAPN1/VCL/YWHAE/HBB/KRT23/HP/SERPINA3/ORM1/SERPINB1/LCN2/S100A14/GSN/IDE/AGA/PSMA3/EEF1G/MDH2/PNP/CSTB/ALDOC/KRT15/FLG/PERP/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP1/LAMP2/PPIB/RPS3/ATP5A1/S100A11/CAPG/CAPZB/PSMB3/GDI2/ARPC4/ACTR2/NPC2/CALML5/PIP/MUC7/KRT1/KRT2/KRT10/FLG2/DEFA3/KRT85 +GO:0043230 extracellular organelle 130 130/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/AZGP1/PLEC/TGM3/KRT13/HRNR/KRT6B/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/LGALS7B/BLMH/FLNB/SOD1/HSPB1/HSPA8/EIF4A1/PPIA/YWHAZ/GGH/GSTP1/LCN1/SERPINB4/C1orf68/SBSN/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/HBB/A2ML1/HP/SERPINA3/ORM1/IL1RN/SPRR1B/SERPINB1/LCN2/CST6/S100A14/GSN/AGA/PSMA3/EEF1G/SERPINB5/MDH2/FCGBP/PNP/CSTB/ALDOC/KRT15/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP1/LAMP2/PPIB/RPS3/ATP5A1/CALML3/S100A11/CAPG/CAPZB/GSS/PSMB3/GDI2/ARPC4/ACTR2/NPC2/AMY1A/AMY1B/AMY1C/CALML5/PIP/ZG16B/CST4/MUC7/KRT1/KRT2/KRT10/FLG2/KPRP/DCD/DEFA3 +GO:0044422 organelle part 103 103/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/PLEC/KRT80/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/POF1B/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/CTSD/UBA52/DMBT1/FLNB/SOD1/HSPB1/HSPA8/EPPK1/PPIA/YWHAZ/GGH/GSTP1/CTSV/ALDOA/CAPN1/VCL/YWHAE/HBB/KRT23/HP/SERPINA3/ORM1/SERPINB1/LCN2/S100A14/GSN/IDE/AGA/PSMA3/MDH2/PNP/CSTB/ALDOC/KRT15/FLG/SERPINB13/CTSB/RPSA/LAMP1/LAMP2/PPIB/RPS3/ATP5A1/S100A11/CAPG/CAPZB/PSMB3/GDI2/ARPC4/ACTR2/NPC2/CALML5/MUC7/KRT1/KRT2/KRT10/FLG2/DEFA3/KRT85 +GO:0097597 ventral disc 0 0/153 +GO:0099572 postsynaptic specialization 1 1/153 ACTR2 +GO:0018995 host 2 2/153 UBA52/MUC7 +GO:0044217 other organism part 3 3/153 LTF/UBA52/MUC7 +GO:0033643 host cell part 1 1/153 MUC7 +GO:0043655 extracellular space of host 0 0/153 +GO:0044216 other organism cell 3 3/153 LTF/UBA52/MUC7 +GO:0044279 other organism membrane 2 2/153 LTF/MUC7 +GO:0085036 extrahaustorial matrix 0 0/153 +GO:0085040 extra-invasive hyphal space 0 0/153 +GO:0005577 fibrinogen complex 0 0/153 +GO:0005601 classical-complement-pathway C3/C5 convertase complex 0 0/153 +GO:0005602 complement component C1 complex 0 0/153 +GO:0005615 extracellular space 140 140/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/AZGP1/PLEC/TGM3/KRT13/HRNR/KRT6B/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/SERPINB7/LYZ/TUBA1B/SERPINA1/HSP90AA1/IL36G/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/CPA4/LGALS7B/BLMH/PLBD1/FLNB/SOD1/HSPB1/HSPA8/EIF4A1/PPIA/YWHAZ/GGH/GSTP1/LCN1/SERPINB4/C1orf68/SBSN/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/HBB/A2ML1/HP/SERPINA3/ORM1/IL1RN/SPRR1B/SERPINB1/LCN2/CST6/S100A14/GSN/IDE/AGA/PSMA3/EEF1G/SERPINB5/MDH2/FCGBP/LYPD3/PNP/CSTB/ALDOC/KRT15/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP1/LAMP2/PPIB/RPS3/ATP5A1/CALML3/S100A11/CAPG/CAPZB/GSS/PSMB3/GDI2/ARPC4/ACTR2/NPC2/AMY1A/AMY1B/AMY1C/CALML5/PIP/ZG16B/CST4/MUC7/CST1/CST2/KRT1/KRT2/KRT10/FLG2/KPRP/SERPINA12/DCD/DEFA3/KRT85 +GO:0005616 larval serum protein complex 0 0/153 +GO:0010367 extracellular isoamylase complex 0 0/153 +GO:0016942 insulin-like growth factor binding protein complex 0 0/153 +GO:0020004 symbiont-containing vacuolar space 0 0/153 +GO:0020005 symbiont-containing vacuole membrane 0 0/153 +GO:0020006 symbiont-containing vacuolar membrane network 0 0/153 +GO:0031012 extracellular matrix 32 32/153 DSP/DSG1/ANXA2/JUP/ACTG1/CASP14/AZGP1/PLEC/LMNA/HSPA5/S100A7/PKM/PRDX1/CSTA/GAPDH/EEF2/MYH9/TUBB4B/SERPINA1/CTSD/FLNB/SOD1/HSPB1/HSPA8/EIF4A1/SBSN/ORM1/SERPINB1/RPS3/ATP5A1/KRT1/DCD +GO:0031395 bursicon neuropeptide hormone complex 0 0/153 +GO:0032311 angiogenin-PRI complex 0 0/153 +GO:0034358 plasma lipoprotein particle 0 0/153 +GO:0035182 female germline ring canal outer rim 0 0/153 +GO:0035183 female germline ring canal inner rim 0 0/153 +GO:0036117 hyaluranon cable 0 0/153 +GO:0042571 immunoglobulin complex, circulating 0 0/153 +GO:0043245 extraorganismal space 0 0/153 +GO:0043511 inhibin complex 0 0/153 +GO:0043514 interleukin-12 complex 0 0/153 +GO:0044420 extracellular matrix component 1 1/153 ANXA2 +GO:0045171 intercellular bridge 0 0/153 +GO:0048180 activin complex 0 0/153 +GO:0061696 pituitary gonadotropin complex 0 0/153 +GO:0070289 extracellular ferritin complex 0 0/153 +GO:0070701 mucus layer 0 0/153 +GO:0070743 interleukin-23 complex 0 0/153 +GO:0070744 interleukin-27 complex 0 0/153 +GO:0070745 interleukin-35 complex 0 0/153 +GO:0072562 blood microparticle 13 13/153 ALB/ACTG1/TF/HSPA1A/HSPA1B/HSPA8/YWHAZ/HBB/HP/SERPINA3/ORM1/GSN/KRT1 +GO:0097058 CRLF-CLCF1 complex 0 0/153 +GO:0097059 CNTFR-CLCF1 complex 0 0/153 +GO:0097619 PTEX complex 0 0/153 +GO:1990296 scaffoldin complex 0 0/153 +GO:1990563 extracellular exosome complex 0 0/153 +GO:1990903 extracellular ribonucleoprotein complex 0 0/153 +GO:0000313 organellar ribosome 0 0/153 +GO:0030094 plasma membrane-derived photosystem I 0 0/153 +GO:0030096 plasma membrane-derived thylakoid photosystem II 0 0/153 +GO:0031300 intrinsic component of organelle membrane 1 1/153 LAMP2 +GO:0031676 plasma membrane-derived thylakoid membrane 0 0/153 +GO:0032420 stereocilium 0 0/153 +GO:0032426 stereocilium tip 0 0/153 +GO:0044232 organelle membrane contact site 0 0/153 +GO:0044441 ciliary part 0 0/153 +GO:0044446 intracellular organelle part 101 101/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/KRT80/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/POF1B/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/CTSD/UBA52/DMBT1/FLNB/SOD1/HSPB1/HSPA8/EPPK1/PPIA/YWHAZ/GGH/GSTP1/CTSV/ALDOA/CAPN1/VCL/YWHAE/HBB/KRT23/HP/SERPINA3/ORM1/SERPINB1/LCN2/S100A14/GSN/IDE/AGA/PSMA3/MDH2/PNP/CSTB/ALDOC/KRT15/FLG/SERPINB13/CTSB/RPSA/LAMP1/LAMP2/PPIB/RPS3/ATP5A1/S100A11/CAPG/CAPZB/PSMB3/GDI2/ARPC4/ACTR2/NPC2/CALML5/MUC7/KRT1/KRT2/KRT10/FLG2/DEFA3/KRT85 +GO:0044449 contractile fiber part 9 9/153 JUP/ENO1/PLEC/ACTN4/FLNB/HSPB1/ALDOA/VCL/CAPZB +GO:0044461 bacterial-type flagellum part 0 0/153 +GO:0044695 Dsc E3 ubiquitin ligase complex 0 0/153 +GO:0048493 plasma membrane-derived thylakoid ribulose bisphosphate carboxylase complex 0 0/153 +GO:0060091 kinocilium 0 0/153 +GO:0060171 stereocilium membrane 0 0/153 +GO:0097591 ventral disc lateral crest 0 0/153 +GO:0097592 ventral disc overlap zone 0 0/153 +GO:0097593 ventral disc microtubule array 0 0/153 +GO:0097594 ventral disc dorsal microribbon 0 0/153 +GO:0097595 ventral disc crossbridge 0 0/153 +GO:0097596 ventral disc supernumerary microtubule array 0 0/153 +GO:0098576 lumenal side of membrane 1 1/153 HSPA8 +GO:0098892 extrinsic component of postsynaptic specialization membrane 0 0/153 +GO:0098948 intrinsic component of postsynaptic specialization membrane 0 0/153 +GO:0099091 postsynaptic specialization, intracellular component 0 0/153 +GO:0099634 postsynaptic specialization membrane 0 0/153 +GO:0120043 stereocilium shaft 0 0/153 +GO:0120044 stereocilium base 0 0/153 +GO:1990070 TRAPPI protein complex 0 0/153 +GO:1990121 H-NS complex 0 0/153 +GO:1990177 IHF-DNA complex 0 0/153 +GO:1990178 HU-DNA complex 0 0/153 +GO:1990500 eif4e-cup complex 0 0/153 +GO:0019013 viral nucleocapsid 0 0/153 +GO:0019015 viral genome 0 0/153 +GO:0019028 viral capsid 0 0/153 +GO:0019033 viral tegument 0 0/153 +GO:0036338 viral membrane 0 0/153 +GO:0039624 viral outer capsid 0 0/153 +GO:0039625 viral inner capsid 0 0/153 +GO:0039626 viral intermediate capsid 0 0/153 +GO:0046727 capsomere 0 0/153 +GO:0046729 viral procapsid 0 0/153 +GO:0046798 viral portal complex 0 0/153 +GO:0046806 viral scaffold 0 0/153 +GO:0098015 virus tail 0 0/153 +GO:0098019 virus tail, major subunit 0 0/153 +GO:0098020 virus tail, minor subunit 0 0/153 +GO:0098021 viral capsid, decoration 0 0/153 +GO:0098023 virus tail, tip 0 0/153 +GO:0098024 virus tail, fiber 0 0/153 +GO:0098025 virus tail, baseplate 0 0/153 +GO:0098026 virus tail, tube 0 0/153 +GO:0098027 virus tail, sheath 0 0/153 +GO:0098028 virus tail, shaft 0 0/153 +GO:0098029 icosahedral viral capsid, spike 0 0/153 +GO:0098030 icosahedral viral capsid, neck 0 0/153 +GO:0098031 icosahedral viral capsid, collar 0 0/153 +GO:0098061 viral capsid, internal space 0 0/153 +GO:0000136 alpha-1,6-mannosyltransferase complex 0 0/153 +GO:0019898 extrinsic component of membrane 6 6/153 ANXA2/JUP/TGM3/ANXA1/TF/DMBT1 +GO:0000506 glycosylphosphatidylinositol-N-acetylglucosaminyltransferase (GPI-GnT) complex 0 0/153 +GO:0000835 ER ubiquitin ligase complex 0 0/153 +GO:0005640 nuclear outer membrane 0 0/153 +GO:0005942 phosphatidylinositol 3-kinase complex 0 0/153 +GO:0008250 oligosaccharyltransferase complex 0 0/153 +GO:0009654 photosystem II oxygen evolving complex 0 0/153 +GO:0009923 fatty acid elongase complex 0 0/153 +GO:0030964 NADH dehydrogenase complex 0 0/153 +GO:0031211 endoplasmic reticulum palmitoyltransferase complex 0 0/153 +GO:0031224 intrinsic component of membrane 10 10/153 DSG1/PIGR/HSPA5/MYH9/FLNB/DSC3/LYPD3/PERP/LAMP1/LAMP2 +GO:0031502 dolichyl-phosphate-mannose-protein mannosyltransferase complex 0 0/153 +GO:0042765 GPI-anchor transamidase complex 0 0/153 +GO:0044453 nuclear membrane part 0 0/153 +GO:0044455 mitochondrial membrane part 1 1/153 ATP5A1 +GO:0044459 plasma membrane part 17 17/153 DSP/DSG1/ANXA2/JUP/PIGR/TGM3/ANXA1/TF/MYH9/HSP90AA1/EPPK1/CTSV/LYPD3/PERP/LAMP1/RPS3/PIP +GO:0045281 succinate dehydrogenase complex 0 0/153 +GO:0046696 lipopolysaccharide receptor complex 0 0/153 +GO:0070057 prospore membrane spindle pole body attachment site 0 0/153 +GO:0070469 respiratory chain 0 0/153 +GO:0071595 Nem1-Spo7 phosphatase complex 0 0/153 +GO:0097478 leaflet of membrane bilayer 0 0/153 +GO:0098552 side of membrane 8 8/153 DSG1/JUP/TGM3/ANXA1/TF/HSPA8/CTSV/LAMP1 +GO:0098796 membrane protein complex 3 3/153 JUP/MYH9/ATP5A1 +GO:1902495 transmembrane transporter complex 0 0/153 +GO:1990332 Ire1 complex 0 0/153 +GO:0008021 synaptic vesicle 1 1/153 LAMP1 +GO:0030129 clathrin coat of synaptic vesicle 0 0/153 +GO:0030672 synaptic vesicle membrane 0 0/153 +GO:0034592 synaptic vesicle lumen 0 0/153 +GO:0044326 dendritic spine neck 0 0/153 +GO:0044327 dendritic spine head 0 0/153 +GO:0048786 presynaptic active zone 0 0/153 +GO:0061846 dendritic spine cytoplasm 0 0/153 +GO:0071212 subsynaptic reticulum 0 0/153 +GO:0097060 synaptic membrane 0 0/153 +GO:0097444 spine apparatus 0 0/153 +GO:0097445 presynaptic active zone dense projection 0 0/153 +GO:0098563 intrinsic component of synaptic vesicle membrane 0 0/153 +GO:0098682 arciform density 0 0/153 +GO:0098793 presynapse 2 2/153 HSPA8/LAMP1 +GO:0098794 postsynapse 1 1/153 ACTR2 +GO:0098830 presynaptic endosome 0 0/153 +GO:0098831 presynaptic active zone cytoplasmic component 0 0/153 +GO:0098833 presynaptic endocytic zone 0 0/153 +GO:0098834 presynaptic endocytic zone cytoplasmic component 0 0/153 +GO:0098843 postsynaptic endocytic zone 0 0/153 +GO:0098845 postsynaptic endosome 0 0/153 +GO:0098850 extrinsic component of synaptic vesicle membrane 0 0/153 +GO:0098895 postsynaptic endosome membrane 0 0/153 +GO:0098897 spine apparatus membrane 0 0/153 +GO:0098899 spine apparatus lumen 0 0/153 +GO:0098929 extrinsic component of spine apparatus membrane 0 0/153 +GO:0098949 intrinsic component of postsynaptic endosome membrane 0 0/153 +GO:0098952 intrinsic component of spine apparatus membrane 0 0/153 +GO:0098954 presynaptic endosome membrane 0 0/153 +GO:0098955 intrinsic component of presynaptic endosome membrane 0 0/153 +GO:0098965 extracellular matrix of synaptic cleft 0 0/153 +GO:0098999 extrinsic component of postsynaptic endosome membrane 0 0/153 +GO:0099007 extrinsic component of presynaptic endosome membrane 0 0/153 +GO:0099240 intrinsic component of synaptic membrane 0 0/153 +GO:0099243 extrinsic component of synaptic membrane 0 0/153 +GO:0099523 presynaptic cytosol 0 0/153 +GO:0099524 postsynaptic cytosol 0 0/153 +GO:0099569 presynaptic cytoskeleton 0 0/153 +GO:0099571 postsynaptic cytoskeleton 0 0/153 +GO:0099631 postsynaptic endocytic zone cytoplasmic component 0 0/153 +GO:0150004 dendritic spine origin 0 0/153 +GO:1990013 presynaptic grid 0 0/153 +GO:1990780 cytoplasmic side of dendritic spine plasma membrane 0 0/153 +GO:0005622 intracellular 133 133/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/AZGP1/PLEC/KRT80/TGM3/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/POF1B/SERPINB7/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/LGALS7B/BLMH/PLBD1/FLNB/SOD1/HSPB1/HSPA8/EPPK1/EIF4A1/PPIA/YWHAZ/GGH/ALOX12B/GSTP1/SERPINB4/C1orf68/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/HBB/KRT23/HP/SERPINA3/ORM1/IL1RN/SPRR1B/SERPINB1/LCN2/S100A14/GSN/IDE/AGA/PSMA3/EEF1G/SERPINB5/MDH2/PNP/CSTB/ALDOC/KRT15/FLG/PERP/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP1/LAMP2/TYMP/PPIB/RPS3/ATP5A1/S100A11/CAPG/HAL/CAPZB/GSS/PSMB3/GDI2/ARPC4/ACTR2/NPC2/CALML5/PIP/MUC7/KRT1/KRT2/KRT10/FLG2/KPRP/SPRR2E/DEFA3/KRT85 +GO:0005642 annulate lamellae 0 0/153 +GO:0005905 clathrin-coated pit 1 1/153 TF +GO:0005933 cellular bud 0 0/153 +GO:0005966 cyclic-nucleotide phosphodiesterase complex 0 0/153 +GO:0008287 protein serine/threonine phosphatase complex 0 0/153 +GO:0009344 nitrite reductase complex [NAD(P)H] 0 0/153 +GO:0009347 aspartate carbamoyltransferase complex 0 0/153 +GO:0009349 riboflavin synthase complex 0 0/153 +GO:0009358 polyphosphate kinase complex 0 0/153 +GO:0009930 longitudinal side of cell surface 0 0/153 +GO:0009986 cell surface 10 10/153 ANXA2/LTF/ENO1/ANXA1/HSPA5/TF/MYH9/CTSV/IDE/LAMP1 +GO:0012505 endomembrane system 69 69/153 DSP/ALB/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/FABP5/PIGR/HRNR/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SERPINB12/PKM/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/TUBB4B/LYZ/SERPINA1/HSP90AA1/ACTN4/CTSD/UBA52/DMBT1/SOD1/HSPA8/PPIA/GGH/GSTP1/CTSV/ALDOA/CAPN1/VCL/HBB/HP/SERPINA3/ORM1/SERPINB1/LCN2/GSN/AGA/EEF1G/PNP/CSTB/ALDOC/PERP/APOD/CTSB/LAMP1/LAMP2/PPIB/RPS3/S100A11/GDI2/ACTR2/NPC2/CALML5/MUC7/KRT1/FLG2/DEFA3 +GO:0015627 type II protein secretion system complex 0 0/153 +GO:0019008 molybdopterin synthase complex 0 0/153 +GO:0020007 apical complex 0 0/153 +GO:0020008 rhoptry 0 0/153 +GO:0020031 polar ring of apical complex 0 0/153 +GO:0020032 basal ring of apical complex 0 0/153 +GO:0020039 pellicle 0 0/153 +GO:0030256 type I protein secretion system complex 0 0/153 +GO:0030257 type III protein secretion system complex 0 0/153 +GO:0030312 external encapsulating structure 0 0/153 +GO:0030427 site of polarized growth 1 1/153 YWHAE +GO:0030428 cell septum 0 0/153 +GO:0030496 midbody 3 3/153 ANXA2/HSPA5/CAPG +GO:0030904 retromer complex 0 0/153 +GO:0030905 retromer, tubulation complex 0 0/153 +GO:0030906 retromer, cargo-selective complex 0 0/153 +GO:0031252 cell leading edge 7 7/153 ANXA2/MYH9/HSP90AA1/GSN/RPS3/S100A11/ACTR2 +GO:0031254 cell trailing edge 1 1/153 MYH9 +GO:0031317 tripartite ATP-independent periplasmic transporter complex 0 0/153 +GO:0031521 spitzenkorper 0 0/153 +GO:0031522 cell envelope Sec protein transport complex 0 0/153 +GO:0031912 oral apparatus 0 0/153 +GO:0031975 envelope 10 10/153 LMNA/ANXA1/CAT/ARG1/GAPDH/UBA52/SOD1/MDH2/RPS3/ATP5A1 +GO:0032126 eisosome 0 0/153 +GO:0032153 cell division site 1 1/153 MYH9 +GO:0032155 cell division site part 1 1/153 MYH9 +GO:0032179 germ tube 0 0/153 +GO:0032766 NHE3/E3KARP/ACTN4 complex 0 0/153 +GO:0033016 rhoptry membrane 0 0/153 +GO:0033104 type VI protein secretion system complex 0 0/153 +GO:0033774 basal labyrinth 0 0/153 +GO:0034591 rhoptry lumen 0 0/153 +GO:0035748 myelin sheath abaxonal region 0 0/153 +GO:0035749 myelin sheath adaxonal region 1 1/153 ANXA2 +GO:0036375 Kibra-Ex-Mer complex 0 0/153 +GO:0042597 periplasmic space 0 0/153 +GO:0042763 intracellular immature spore 0 0/153 +GO:0042995 cell projection 20 20/153 ANXA2/ANXA1/PKM/ARG1/MYH9/HSP90AA1/ACTN4/FLNB/SOD1/HSPB1/EPPK1/CTSV/YWHAE/GSN/APOD/LAMP1/RPS3/S100A11/ARPC4/ACTR2 +GO:0043209 myelin sheath 14 14/153 ALB/ANXA2/ACTG1/HSPA5/PKM/PRDX1/TUBB4B/TUBA1B/HSP90AA1/SOD1/HSPA8/GSN/MDH2/ATP5A1 +GO:0043218 compact myelin 1 1/153 ANXA2 +GO:0043219 lateral loop 0 0/153 +GO:0043220 Schmidt-Lanterman incisure 1 1/153 ANXA2 +GO:0043684 type IV secretion system complex 0 0/153 +GO:0044099 polar tube 0 0/153 +GO:0044297 cell body 6 6/153 ARG1/FLNB/SOD1/CTSV/APOD/LAMP1 +GO:0044424 intracellular part 133 133/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT78/KRT17/FABP5/CASP14/PIGR/ENO1/AZGP1/PLEC/KRT80/TGM3/KRT13/HRNR/KRT6B/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/ARG1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/POF1B/SERPINB7/LYZ/TUBA1B/SERPINA1/HSP90AA1/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/LGALS7B/BLMH/PLBD1/FLNB/SOD1/HSPB1/HSPA8/EPPK1/EIF4A1/PPIA/YWHAZ/GGH/ALOX12B/GSTP1/SERPINB4/C1orf68/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/HBB/KRT23/HP/SERPINA3/ORM1/IL1RN/SPRR1B/SERPINB1/LCN2/S100A14/GSN/IDE/AGA/PSMA3/EEF1G/SERPINB5/MDH2/PNP/CSTB/ALDOC/KRT15/FLG/PERP/SERPINB13/APOD/KLK1/CTSB/RPSA/LAMP1/LAMP2/TYMP/PPIB/RPS3/ATP5A1/S100A11/CAPG/HAL/CAPZB/GSS/PSMB3/GDI2/ARPC4/ACTR2/NPC2/CALML5/PIP/MUC7/KRT1/KRT2/KRT10/FLG2/KPRP/SPRR2E/DEFA3/KRT85 +GO:0044457 cell septum part 0 0/153 +GO:0044462 external encapsulating structure part 0 0/153 +GO:0044463 cell projection part 5 5/153 HSP90AA1/SOD1/HSPB1/YWHAE/RPS3 +GO:0044697 HICS complex 0 0/153 +GO:0045177 apical part of cell 5 5/153 DSG1/ANXA1/TF/CTSV/PIP +GO:0045178 basal part of cell 1 1/153 TF +GO:0051286 cell tip 0 0/153 +GO:0060187 cell pole 0 0/153 +GO:0061835 ventral surface of cell 0 0/153 +GO:0070056 prospore membrane leading edge 0 0/153 +GO:0070258 inner membrane complex 0 0/153 +GO:0070331 CD20-Lck-Fyn complex 0 0/153 +GO:0070332 CD20-Lck-Lyn-Fyn complex 0 0/153 +GO:0070938 contractile ring 1 1/153 MYH9 +GO:0071944 cell periphery 59 59/153 DSP/DSG1/ANXA2/JUP/MUC5B/ACTG1/KRT17/FABP5/PIGR/ENO1/AZGP1/PLEC/TGM3/HRNR/ANXA1/HSPA5/TF/CAT/SERPINB12/CSTA/GAPDH/EEF2/MYH9/HSP90AA1/ACTN4/UBA52/FLNB/SOD1/HSPB1/HSPA8/EPPK1/GSTP1/DSC3/C1orf68/CTSV/CAPN1/VCL/YWHAE/IL1RN/SPRR1B/CST6/GSN/IDE/LYPD3/FLG/PERP/RPSA/LAMP1/LAMP2/RPS3/ATP5A1/ACTR2/PIP/MUC7/KRT1/KRT2/KRT10/SERPINA12/SPRR2E +GO:0072324 ascus epiplasm 0 0/153 +GO:0090543 Flemming body 1 1/153 CAPG +GO:0090635 extracellular core region of desmosome 0 0/153 +GO:0090636 outer dense plaque of desmosome 0 0/153 +GO:0090637 inner dense plaque of desmosome 0 0/153 +GO:0097223 sperm part 1 1/153 ALDOA +GO:0097268 cytoophidium 0 0/153 +GO:0097458 neuron part 11 11/153 ARG1/ACTN4/FLNB/SOD1/HSPB1/HSPA8/CTSV/YWHAE/APOD/LAMP1/ACTR2 +GO:0097569 lateral shield 0 0/153 +GO:0097574 lateral part of cell 0 0/153 +GO:0097610 cell surface furrow 1 1/153 MYH9 +GO:0097613 dinoflagellate epicone 0 0/153 +GO:0097614 dinoflagellate hypocone 0 0/153 +GO:0097653 unencapsulated part of cell 0 0/153 +GO:0097683 dinoflagellate apex 0 0/153 +GO:0097684 dinoflagellate antapex 0 0/153 +GO:0098046 type V protein secretion system complex 0 0/153 +GO:0098862 cluster of actin-based cell projections 4 4/153 PLEC/MYH9/ACTN4/FLNB +GO:0140022 cnida 0 0/153 +GO:1990015 ensheathing process 0 0/153 +GO:1990016 neck portion of tanycyte 0 0/153 +GO:1990018 tail portion of tanycyte 0 0/153 +GO:1990065 Dxr protein complex 0 0/153 +GO:1990204 oxidoreductase complex 0 0/153 +GO:1990225 rhoptry neck 0 0/153 +GO:1990455 PTEN phosphatase complex 0 0/153 +GO:1990722 DAPK1-calmodulin complex 0 0/153 +GO:1990794 basolateral part of cell 0 0/153 +GO:0031594 neuromuscular junction 1 1/153 MYH9 +GO:0044456 synapse part 3 3/153 HSPA8/LAMP1/ACTR2 +GO:0060076 excitatory synapse 0 0/153 +GO:0060077 inhibitory synapse 0 0/153 +GO:0097470 ribbon synapse 0 0/153 +GO:0098685 Schaffer collateral - CA1 synapse 0 0/153 +GO:0098686 hippocampal mossy fiber to CA3 synapse 0 0/153 +GO:0098690 glycinergic synapse 0 0/153 +GO:0098691 dopaminergic synapse 0 0/153 +GO:0098692 noradrenergic synapse 0 0/153 +GO:0098978 glutamatergic synapse 0 0/153 +GO:0098979 polyadic synapse 0 0/153 +GO:0098981 cholinergic synapse 0 0/153 +GO:0098982 GABA-ergic synapse 0 0/153 +GO:0098984 neuron to neuron synapse 1 1/153 ACTR2 +GO:0099154 serotonergic synapse 0 0/153 +GO:0009506 plasmodesma 0 0/153 +GO:0005818 aster 0 0/153 +GO:0097740 paraflagellar rod 0 0/153 +GO:0097741 mastigoneme 0 0/153 +GO:0098644 complex of collagen trimers 0 0/153 +GO:0099081 supramolecular polymer 31 31/153 DSP/KRT6A/KRT16/JUP/ACTG1/KRT78/KRT17/CASP14/ENO1/PLEC/KRT80/KRT13/KRT6B/LMNA/TUBB4B/POF1B/TUBA1B/ACTN4/FLNB/HSPB1/EPPK1/ALDOA/VCL/KRT23/KRT15/FLG/CAPZB/KRT1/KRT2/KRT10/KRT85
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/cluster_profiler_GGO_MF.csv Tue Dec 18 09:21:32 2018 -0500 @@ -0,0 +1,155 @@ +ID Description Count GeneRatio geneID +GO:0004133 glycogen debranching enzyme activity 0 0/153 +GO:0016491 oxidoreductase activity 11 11/153 CAT/PRDX1/GAPDH/LDHA/TXN/SOD1/ALOX12B/GSTP1/PGK1/HBB/MDH2 +GO:0008987 quinolinate synthetase A activity 0 0/153 +GO:0009975 cyclase activity 0 0/153 +GO:0010280 UDP-L-rhamnose synthase activity 0 0/153 +GO:0016740 transferase activity 10 10/153 TGM3/PKM/GAPDH/HSP90AA1/GGCT/GSTP1/PGK1/EEF1G/PNP/TYMP +GO:0016787 hydrolase activity 37 37/153 LTF/CASP14/AZGP1/ANXA1/HSPA5/CAT/ARG1/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/LYZ/TUBA1B/HSP90AA1/CTSD/CPA4/BLMH/PLBD1/HSPA8/EIF4A1/GGH/CTSV/CAPN1/IDE/AGA/PSMA3/KLK1/CTSB/RPS3/ATP5A1/PSMB3/AMY1A/AMY1B/AMY1C/PIP/DCD +GO:0016829 lyase activity 5 5/153 ENO1/ALDOA/ALDOC/RPS3/HAL +GO:0016853 isomerase activity 3 3/153 TPI1/PPIA/PPIB +GO:0016874 ligase activity 1 1/153 GSS +GO:0032451 demethylase activity 0 0/153 +GO:0046572 versicolorin B synthase activity 0 0/153 +GO:0046905 phytoene synthase activity 0 0/153 +GO:0061783 peptidoglycan muralytic activity 1 1/153 LYZ +GO:0070283 radical SAM enzyme activity 0 0/153 +GO:0140096 catalytic activity, acting on a protein 22 22/153 LTF/CASP14/TGM3/GAPDH/HSP90AA1/GGCT/CTSD/CPA4/BLMH/PPIA/GGH/CTSV/CAPN1/IDE/AGA/PSMA3/KLK1/CTSB/PPIB/PSMB3/PIP/DCD +GO:0140097 catalytic activity, acting on DNA 2 2/153 ANXA1/RPS3 +GO:0140098 catalytic activity, acting on RNA 2 2/153 AZGP1/EIF4A1 +GO:1990055 phenylacetaldehyde synthase activity 0 0/153 +GO:0000156 phosphorelay response regulator activity 0 0/153 +GO:0004879 nuclear receptor activity 0 0/153 +GO:0004708 MAP kinase kinase activity 0 0/153 +GO:0005057 signal transducer activity, downstream of receptor 0 0/153 +GO:0005068 transmembrane receptor protein tyrosine kinase adaptor activity 0 0/153 +GO:0030297 transmembrane receptor protein tyrosine kinase activator activity 0 0/153 +GO:0008086 light-activated voltage-gated calcium channel activity 0 0/153 +GO:0008384 IkappaB kinase activity 0 0/153 +GO:0009927 histidine phosphotransfer kinase activity 0 0/153 +GO:0038023 signaling receptor activity 3 3/153 KRT17/PIGR/DMBT1 +GO:0038078 MAP kinase phosphatase activity involved in regulation of innate immune response 0 0/153 +GO:0097199 cysteine-type endopeptidase activity involved in apoptotic signaling pathway 0 0/153 +GO:0099107 ion channel regulator activity involved in G-protein coupled receptor signaling pathway 0 0/153 +GO:1990890 netrin receptor binding 0 0/153 +GO:0003735 structural constituent of ribosome 3 3/153 UBA52/RPSA/RPS3 +GO:0005199 structural constituent of cell wall 1 1/153 JUP +GO:0005200 structural constituent of cytoskeleton 11 11/153 DSP/KRT16/ACTG1/KRT17/KRT6B/TUBB4B/TUBA1B/KRT15/ARPC4/ACTR2/KRT2 +GO:0005201 extracellular matrix structural constituent 0 0/153 +GO:0005212 structural constituent of eye lens 0 0/153 +GO:0005213 structural constituent of chorion 0 0/153 +GO:0008147 structural constituent of bone 0 0/153 +GO:0008307 structural constituent of muscle 1 1/153 PLEC +GO:0016490 structural constituent of peritrophic membrane 0 0/153 +GO:0017056 structural constituent of nuclear pore 0 0/153 +GO:0019911 structural constituent of myelin sheath 0 0/153 +GO:0030280 structural constituent of epidermis 5 5/153 FLG/KRT1/KRT2/KRT10/SPRR2E +GO:0030527 structural constituent of chromatin 0 0/153 +GO:0032947 protein complex scaffold activity 0 0/153 +GO:0035804 structural constituent of egg coat 0 0/153 +GO:0039660 structural constituent of virion 0 0/153 +GO:0042302 structural constituent of cuticle 0 0/153 +GO:0043886 structural constituent of carboxysome 0 0/153 +GO:0097099 structural constituent of albumen 0 0/153 +GO:0097493 structural molecule activity conferring elasticity 0 0/153 +GO:0098918 structural constituent of synapse 0 0/153 +GO:0005344 oxygen carrier activity 1 1/153 HBB +GO:0022857 transmembrane transporter activity 3 3/153 AZGP1/TF/ATP5A1 +GO:0005326 neurotransmitter transporter activity 0 0/153 +GO:0005487 nucleocytoplasmic transporter activity 0 0/153 +GO:0051183 vitamin transporter activity 0 0/153 +GO:0051184 cofactor transporter activity 0 0/153 +GO:0017089 glycolipid transporter activity 0 0/153 +GO:0022892 substrate-specific transporter activity 5 5/153 AZGP1/TF/APOD/ATP5A1/NPC2 +GO:0034202 glycolipid-translocating activity 0 0/153 +GO:0034437 glycoprotein transporter activity 0 0/153 +GO:0038024 cargo receptor activity 1 1/153 DMBT1 +GO:0043563 odorant transporter activity 0 0/153 +GO:0090484 drug transporter activity 0 0/153 +GO:0098748 endocytic adaptor activity 0 0/153 +GO:1990833 clathrin-uncoating ATPase activity 0 0/153 +GO:0000035 acyl binding 0 0/153 +GO:0005515 protein binding 126 126/153 DSP/KRT6A/ALB/KRT16/DSG1/ANXA2/JUP/LTF/MUC5B/SERPINB3/ACTG1/KRT17/FABP5/CASP14/ENO1/AZGP1/PLEC/KRT80/KRT13/KRT6B/LMNA/ANXA1/HSPA5/TF/CAT/S100A7/SFN/SERPINB12/PKM/TPI1/PRDX1/CSTA/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/POF1B/LYZ/TUBA1B/SERPINA1/HSP90AA1/IL36G/ACTN4/GGCT/LDHA/CTSD/UBA52/TXN/DMBT1/BLMH/FLNB/SOD1/HSPB1/HSPA8/EPPK1/EIF4A1/PPIA/YWHAZ/ALOX12B/GSTP1/LCN1/SERPINB4/CTSV/PGK1/ALDOA/CAPN1/VCL/YWHAE/HBB/HP/SERPINA3/ORM1/IL1RN/SPRR1B/LCN2/CST6/S100A14/GSN/IDE/AGA/PSMA3/EEF1G/SERPINB5/MDH2/FCGBP/LYPD3/CSTB/ALDOC/KRT15/FLG/SERPINB13/APOD/CTSB/RPSA/LAMP1/LAMP2/TYMP/PPIB/RPS3/ATP5A1/CALML3/S100A11/CAPG/CAPZB/GSS/PSMB3/GDI2/ARPC4/ACTR2/NPC2/AMY1A/AMY1B/AMY1C/PIP/CST4/MUC7/CST1/CST2/KRT1/KRT2/KPRP/DCD/SPRR2E/DEFA3 +GO:0001871 pattern binding 0 0/153 +GO:0003682 chromatin binding 1 1/153 ACTN4 +GO:0003823 antigen binding 0 0/153 +GO:0030246 carbohydrate binding 4 4/153 LGALS7B/ALDOA/ZG16B/KRT1 +GO:0005549 odorant binding 0 0/153 +GO:0008289 lipid binding 8 8/153 ALB/ANXA2/LTF/FABP5/ANXA1/HSPA8/APOD/NPC2 +GO:0008144 drug binding 4 4/153 ALB/PPIA/GSTP1/PNP +GO:0008430 selenium binding 0 0/153 +GO:0019825 oxygen binding 2 2/153 ALB/HBB +GO:0015643 toxic substance binding 2 2/153 ALB/DSG1 +GO:0019808 polyamine binding 0 0/153 +GO:0050840 extracellular matrix binding 2 2/153 ANXA2/LYPD3 +GO:0031409 pigment binding 0 0/153 +GO:0033218 amide binding 5 5/153 PPIA/GSTP1/CTSV/IDE/GSS +GO:0033226 2-aminoethylphosphonate binding 0 0/153 +GO:0035731 dinitrosyl-iron complex binding 1 1/153 GSTP1 +GO:0036094 small molecule binding 28 28/153 ALB/ACTG1/FABP5/HSPA5/CAT/PKM/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/TUBA1B/HSP90AA1/ACTN4/LDHA/HSPA8/EIF4A1/PGK1/ALDOA/LCN2/IDE/PNP/APOD/ATP5A1/GSS/ACTR2/NPC2 +GO:0042165 neurotransmitter binding 1 1/153 IDE +GO:0042562 hormone binding 2 2/153 PKM/IDE +GO:0043167 ion binding 51 51/153 ALB/DSG1/ANXA2/LTF/ACTG1/FABP5/ENO1/TGM3/HRNR/ANXA1/HSPA5/TF/CAT/S100A7/PKM/ARG1/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/TUBA1B/HSP90AA1/ACTN4/CPA4/SOD1/HSPA8/EIF4A1/ALOX12B/GSTP1/LCN1/DSC3/PGK1/CAPN1/HBB/LCN2/S100A14/GSN/IDE/PNP/FLG/ATP5A1/CALML3/S100A11/GSS/ACTR2/AMY1A/AMY1B/AMY1C/CALML5/FLG2 +GO:0043176 amine binding 0 0/153 +GO:0043210 alkanesulfonate binding 0 0/153 +GO:0043287 poly(3-hydroxyalkanoate) binding 0 0/153 +GO:0046812 host cell surface binding 0 0/153 +GO:0044877 macromolecular complex binding 21 21/153 HSPA5/PKM/EEF2/MYH9/POF1B/HSP90AA1/ACTN4/HSPA8/EPPK1/CTSV/YWHAE/GSN/CTSB/RPSA/PPIB/RPS3/CAPG/CAPZB/ARPC4/ACTR2/PIP +GO:0046790 virion binding 1 1/153 PPIA +GO:0046848 hydroxyapatite binding 0 0/153 +GO:0046904 calcium oxalate binding 0 0/153 +GO:0048037 cofactor binding 4 4/153 ALB/CAT/GAPDH/LDHA +GO:0050436 microfibril binding 0 0/153 +GO:0050824 water binding 0 0/153 +GO:0050997 quaternary ammonium group binding 0 0/153 +GO:0051540 metal cluster binding 1 1/153 RPS3 +GO:0060090 molecular adaptor activity 5 5/153 DSP/ANXA1/CSTA/SPRR1B/ARPC4 +GO:0070026 nitric oxide binding 1 1/153 GSTP1 +GO:0072328 alkene binding 0 0/153 +GO:0072341 modified amino acid binding 3 3/153 HSPA8/GSTP1/GSS +GO:0097159 organic cyclic compound binding 50 50/153 DSP/ALB/ANXA2/LTF/ACTG1/ENO1/PLEC/ANXA1/HSPA5/CAT/PKM/PRDX1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/TUBA1B/HSP90AA1/ACTN4/LDHA/TXN/FLNB/HSPB1/HSPA8/EPPK1/EIF4A1/PPIA/YWHAZ/PGK1/ALDOA/YWHAE/HBB/SERPINA3/IDE/EEF1G/MDH2/PNP/CSTB/APOD/RPSA/PPIB/RPS3/ATP5A1/GSS/GDI2/ACTR2/NPC2/DCD +GO:0097243 flavonoid binding 0 0/153 +GO:0097367 carbohydrate derivative binding 21 21/153 LTF/ACTG1/HSPA5/PKM/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/TUBA1B/HSP90AA1/ACTN4/HSPA8/EIF4A1/PGK1/IDE/PNP/CTSB/ATP5A1/GSS/ACTR2 +GO:1901363 heterocyclic compound binding 48 48/153 DSP/ALB/ANXA2/LTF/ACTG1/ENO1/PLEC/ANXA1/HSPA5/CAT/PKM/PRDX1/GAPDH/HSPA1A/HSPA1B/EEF2/MYH9/TUBB4B/TUBA1B/HSP90AA1/ACTN4/LDHA/TXN/FLNB/HSPB1/HSPA8/EPPK1/EIF4A1/PPIA/YWHAZ/PGK1/ALDOA/YWHAE/HBB/SERPINA3/IDE/EEF1G/MDH2/PNP/CSTB/RPSA/PPIB/RPS3/ATP5A1/GSS/GDI2/ACTR2/DCD +GO:1901567 fatty acid derivative binding 0 0/153 +GO:1901681 sulfur compound binding 3 3/153 LTF/GSTP1/GSS +GO:1902670 carbon dioxide binding 0 0/153 +GO:1904012 platinum binding 0 0/153 +GO:1904013 xenon atom binding 0 0/153 +GO:1904483 synthetic cannabinoid binding 0 0/153 +GO:1904493 tetrahydrofolyl-poly(glutamate) polymer binding 0 0/153 +GO:1904517 MgATP(2-) binding 0 0/153 +GO:0004362 glutathione-disulfide reductase activity 0 0/153 +GO:0004601 peroxidase activity 4 4/153 CAT/PRDX1/GSTP1/HBB +GO:0004784 superoxide dismutase activity 1 1/153 SOD1 +GO:0004791 thioredoxin-disulfide reductase activity 1 1/153 TXN +GO:0032542 sulfiredoxin activity 0 0/153 +GO:0045174 glutathione dehydrogenase (ascorbate) activity 0 0/153 +GO:0050605 superoxide reductase activity 0 0/153 +GO:0051920 peroxiredoxin activity 1 1/153 PRDX1 +GO:0004694 eukaryotic translation initiation factor 2alpha kinase activity 0 0/153 +GO:0030371 translation repressor activity 0 0/153 +GO:0044748 3'-5'-exoribonuclease activity involved in mature miRNA 3'-end processing 0 0/153 +GO:0045183 translation factor activity, non-nucleic acid binding 0 0/153 +GO:0090079 translation regulator activity, nucleic acid binding 0 0/153 +GO:0090624 endoribonuclease activity, cleaving miRNA-paired mRNA 0 0/153 +GO:0004679 AMP-activated protein kinase activity 0 0/153 +GO:0004690 cyclic nucleotide-dependent protein kinase activity 0 0/153 +GO:0004872 receptor activity 5 5/153 KRT17/PIGR/DMBT1/RPSA/KRT1 +GO:0017132 cAMP-dependent guanyl-nucleotide exchange factor activity 0 0/153 +GO:0031992 energy transducer activity 0 0/153 +GO:0097472 cyclin-dependent protein kinase activity 0 0/153 +GO:0005085 guanyl-nucleotide exchange factor activity 1 1/153 YWHAE +GO:0016247 channel regulator activity 1 1/153 YWHAE +GO:0030234 enzyme regulator activity 27 27/153 ANXA2/LTF/SERPINB3/ANXA1/SFN/SERPINB12/CSTA/GAPDH/SERPINB7/SERPINA1/HSP90AA1/HSPB1/GSTP1/LCN1/SERPINB4/A2ML1/SERPINA3/SERPINB1/CST6/SERPINB5/CSTB/SERPINB13/GDI2/CST4/CST1/CST2/SERPINA12 +GO:0030545 receptor regulator activity 3 3/153 IL36G/IL1RN/TYMP +GO:0001618 virus receptor activity 6 6/153 SERPINB3/HSPA1A/HSPA1B/IDE/RPSA/LAMP1 +GO:0000036 acyl carrier activity 0 0/153 +GO:0016530 metallochaperone activity 0 0/153 +GO:0036370 D-alanyl carrier activity 0 0/153 +GO:1904091 peptidyl carrier protein activity involved in nonribosomal peptide biosynthesis 0 0/153 +GO:0000988 transcription factor activity, protein binding 3 3/153 JUP/HSPA1A/ACTN4 +GO:0001070 RNA binding transcription regulator activity 0 0/153 +GO:0001072 transcription antitermination factor activity, RNA binding 0 0/153 +GO:0001073 transcription antitermination factor activity, DNA binding 0 0/153 +GO:0003700 DNA binding transcription factor activity 1 1/153 ENO1
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/input_id_list.csv Tue Dec 18 09:21:32 2018 -0500 @@ -0,0 +1,179 @@ +V1 neXtProt_ID Ensembl SeqLength MW IsoPoint TMDomains ProteinExistence Chr SubcellLocations Diseases Gene Gene description RNA tissue category Reliability (IH) RNA TS TPM +A0AVF1 NX_A0AVF1 ENSG00000105948 554 64178 6.5 0 PE1 7 Cytoplasm;Nucleus;Nucleus;Cytoskeleton;Cytoplasm;Cilium NA TTC26 Tetratricopeptide repeat domain 26 Tissue enhanced Supported fallopian tube: 22.4;testis: 22.0 +A1A519 NX_A1A519 ENSG00000164334 330 37158 5 0 PE1 5 Nucleus NA FAM170A Family with sequence similarity 170, member A Tissue enriched Approved testis: 20.8 +A4FU69 NX_A4FU69 ENSG00000176927 1503 173404 5.58 0 PE1 17 NA NA EFCAB5 EF-hand calcium binding domain 5 Tissue enriched Uncertain testis: 15.3 +A5D8V7 NX_A5D8V7 ENSG00000198003 595 69140 9.11 0 PE1 19 Cilium;Cilium basal body;Centriole;Cilium axoneme Ciliary dyskinesia, primary, 30 CCDC151 Coiled-coil domain containing 151 Tissue enhanced Supported fallopian tube: 13.6;parathyroid gland: 7.0;testis: 7.5 +A5D8W1 NX_A5D8W1 ENSG00000105792 941 105883 6.81 0 PE1 7 NA NA CFAP69 Cilia and flagella associated protein 69 Tissue enhanced Uncertain prostate: 24.6 +A6NCJ1 NX_A6NCJ1 ENSG00000183397 209 24176 9.14 0 PE1 19 Cell membrane;Cytoplasm NA C19orf71 Chromosome 19 open reading frame 71 Mixed Uncertain NA +A6NIV6 NX_A6NIV6 ENSG00000188306 560 63977 8.43 0 PE1 3 NA NA LRRIQ4 Leucine-rich repeats and IQ motif containing 4 Tissue enhanced Uncertain testis: 4.3 +A6NJV1 NX_A6NJV1 ENSG00000173557 201 23421 10 0 PE1 2 Cytoplasm;Cytoplasmic vesicle;Nucleus NA C2orf70 Chromosome 2 open reading frame 70 Group enriched Approved fallopian tube: 11.9;stomach: 4.9;testis: 17.5 +A6NNW6 NX_A6NNW6 ENSG00000188316 628 68821 5.7 0 PE1 10 Nucleus NA ENO4 Enolase family member 4 Tissue enhanced Supported fallopian tube: 14.6 +B2RC85 NX_B2RC85 ENSG00000169402 870 100547 7.16 0 PE2 7 NA NA RSPH10B2 Radial spoke head 10 homolog B2 (Chlamydomonas) Group enriched Uncertain fallopian tube: 16.2;testis: 35.7 +O14734 NX_O14734 ENSG00000101473 319 35914 7.22 0 PE1 20 Mitochondrion;Cytoplasmic vesicle;Cytoplasm;Peroxisome matrix NA ACOT8 Acyl-CoA thioesterase 8 Expressed in all Approved NA +O14967 NX_O14967 ENSG00000153132 610 70039 4.58 1 PE1 4 Endoplasmic reticulum;Endoplasmic reticulum membrane NA CLGN Calmegin Tissue enhanced Supported testis: 185.4 +O15371 NX_O15371 ENSG00000100353 548 63973 5.79 0 PE1 22 Cytoplasm;Nucleus;Cytoplasm NA EIF3D Eukaryotic translation initiation factor 3, subunit D Expressed in all Approved NA +O43236 NX_O43236 ENSG00000108387 478 55098 5.77 0 PE1 17 Nucleoplasm;Cytoplasm;Cytoskeleton;Flagellum;Mitochondrion;Nucleus NA SEPT4 Septin 4 Group enriched Supported adrenal gland: 218.2;cerebral cortex: 288.7;spleen: 57.8 +O60733 NX_O60733 ENSG00000184381 806 89903 6.86 0 PE1 22 Cytoplasm;Membrane Neurodegeneration with brain iron accumulation 2A;Parkinson disease 14;Neurodegeneration with brain iron accumulation 2B PLA2G6 Phospholipase A2, group VI (cytosolic, calcium-independent) Expressed in all Approved NA +O75367 NX_O75367 ENSG00000113648 372 39617 9.8 0 PE1 5 Nucleus;Nucleus;Chromosome NA H2AFY H2A histone family, member Y Expressed in all Supported NA +O75425 NX_O75425 ENSG00000106330 235 25519 9.29 2 PE1 7 Nucleoplasm;Cytoplasm;Membrane NA MOSPD3 Motile sperm domain containing 3 Expressed in all Uncertain NA +O75487 NX_O75487 ENSG00000076716 556 62412 6.26 0 PE1 X Cytoplasmic vesicle;Cell membrane;Extracellular space NA GPC4 Glypican 4 Mixed Approved NA +O75610 NX_O75610 ENSG00000243709 366 40880 8.6 0 PE1 1 Secreted NA LEFTY1 Left-right determination factor 1 Tissue enhanced Approved colon: 59.7;rectum: 35.8 +O75787 NX_O75787 ENSG00000182220 350 39008 5.76 1 PE1 X Membrane Parkinsonism with spasticity, X-linked;Mental retardation, X-linked, with epilepsy ATP6AP2 ATPase, H+ transporting, lysosomal accessory protein 2 Expressed in all Approved NA +O95995 NX_O95995 ENSG00000141013 478 56356 7.72 0 PE1 16 Cytoplasm;Cytoskeleton;Flagellum;Cilium axoneme;Cilium basal body;Golgi apparatus Ciliary dyskinesia, primary, 33 GAS8 Growth arrest-specific 8 Mixed Approved NA +P06748 NX_P06748 ENSG00000181163 294 32575 4.64 0 PE1 5 Nucleolus;Nucleus;Nucleus;Nucleolus;Nucleolus;Nucleoplasm;Centrosome NA NPM1 Nucleophosmin (nucleolar phosphoprotein B23, numatrin) Expressed in all Supported NA +P08311ups NA NA NA NA NA NA NA NA NA NA NA NA NA NA NA +P0C221 NX_P0C221 ENSG00000151838 793 93626 6.34 0 PE1 14 NA NA CCDC175 Coiled-coil domain containing 175 Tissue enriched Uncertain testis: 4.0 +P12268 NX_P12268 ENSG00000178035 514 55805 6.44 0 PE1 3 Cytoplasm;Cytoplasm;Nucleus NA IMPDH2 IMP (inosine 5'-monophosphate) dehydrogenase 2 Expressed in all Approved NA +P12956 NX_P12956 ENSG00000196419 609 69843 6.23 0 PE1 22 Nucleus;Nucleoplasm;Nucleus;Chromosome NA XRCC6 X-ray repair complementing defective repair in Chinese hamster cells 6 Expressed in all Supported NA +P21810 NX_P21810 ENSG00000182492 368 41654 7.16 0 PE1 X Golgi apparatus;Extracellular matrix Spondyloepimetaphyseal dysplasia, X-linked BGN Biglycan Mixed Supported NA +P21980 NX_P21980 ENSG00000198959 687 77329 5.11 0 PE1 20 Cytoplasm;Cell membrane;Nucleus NA TGM2 Transglutaminase 2 Tissue enhanced Approved cervix, uterine: 456.8 +P35606 NX_P35606 ENSG00000184432 906 102487 5.15 0 PE1 3 Cytoplasm;Cytosol;Golgi apparatus membrane;COPI-coated vesicle membrane;Golgi apparatus;Cytoplasm NA COPB2 Coatomer protein complex, subunit beta 2 (beta prime) Expressed in all Approved NA +P35663 NX_P35663 ENSG00000183035 651 74242 9.68 0 PE1 X Calyx NA CYLC1 Cylicin, basic protein of sperm head cytoskeleton 1 Tissue enriched Supported testis: 42.7 +P36578 NX_P36578 ENSG00000174444 427 47697 11.07 0 PE1 15 Nucleus;Nucleolus;Cytoplasm NA RPL4 Ribosomal protein L4 Expressed in all Uncertain NA +P39023 NX_P39023 ENSG00000100316 403 46109 10.19 0 PE1 22 Nucleolus;Nucleoplasm;Cytoplasm;Cytoplasm;Nucleolus NA RPL3 Ribosomal protein L3 Expressed in all Uncertain NA +P45880 NX_P45880 ENSG00000165637 294 31567 7.5 0 PE1 10 Mitochondrion;Mitochondrion outer membrane NA VDAC2 Voltage-dependent anion channel 2 Expressed in all Supported NA +P46777 NX_P46777 ENSG00000122406 297 34363 9.73 0 PE1 1 Nucleolus;Cytoplasm;Nucleolus;Cytoplasm Diamond-Blackfan anemia 6 RPL5 Ribosomal protein L5 Expressed in all Approved NA +P46781 NX_P46781 ENSG00000170889; ENSG00000278270; ENSG00000274950; ENSG00000274646 194 22591 10.66 0 PE1 19 Cytoplasm NA RPS9 Ribosomal protein S9 Expressed in all Approved NA +P49327 NX_P49327 ENSG00000169710 2511 273427 6.01 0 PE1 17 Cell membrane;Cytoplasm;Cytoplasm;Melanosome NA FASN Fatty acid synthase Expressed in all Supported NA +P49585 NX_P49585 ENSG00000161217 367 41731 6.82 0 PE1 3 Nucleus;Cytosol;Membrane Spondylometaphyseal dysplasia with cone-rod dystrophy PCYT1A Phosphate cytidylyltransferase 1, choline, alpha Expressed in all Approved NA +P50402 NX_P50402 ENSG00000102119 254 28994 5.29 1 PE1 X Nucleus envelope;Nucleus membrane;Endoplasmic reticulum;Nucleus inner membrane;Nucleus outer membrane Emery-Dreifuss muscular dystrophy 1, X-linked EMD Emerin Expressed in all Supported NA +P50570 NX_P50570 ENSG00000079805 870 98064 7.04 0 PE1 19 Golgi apparatus;Cytoplasm;Cytoplasm;Cytoskeleton;Cell junction;Clathrin-coated pit;Postsynaptic density;Synapse;Midbody;Phagocytic cup;Phagosome membrane Charcot-Marie-Tooth disease, dominant, intermediate type, B;Lethal congenital contracture syndrome 5;Myopathy, centronuclear, 1;Charcot-Marie-Tooth disease 2M DNM2 Dynamin 2 Expressed in all Supported NA +P52272 NX_P52272 ENSG00000099783 730 77516 8.84 0 PE1 19 Nucleus;Nucleoplasm;Nucleolus NA HNRNPM Heterogeneous nuclear ribonucleoprotein M Expressed in all Supported NA +P57740 NX_P57740 ENSG00000111581 925 106374 5.28 0 PE1 12 Nucleoplasm;Centrosome;Nucleus membrane;Nuclear pore complex;Kinetochore Nephrotic syndrome 11 NUP107 Nucleoporin 107kDa Expressed in all Uncertain NA +P61247 NX_P61247 ENSG00000145425 264 29945 9.75 0 PE1 4 Nucleolus;Cytoplasm;Cytoplasm;Nucleus NA RPS3A Ribosomal protein S3A Expressed in all Approved NA +P62241 NX_P62241 ENSG00000142937 208 24205 10.32 0 PE1 1 Nucleus;Nucleolus;Cytoplasm;Cytoplasm;Membrane NA RPS8 Ribosomal protein S8 Expressed in all NA NA +Q00839 NX_Q00839 ENSG00000153187 825 90584 5.76 0 PE1 1 Nucleoplasm;Cytoskeleton;Nucleus;Cytoplasm;Cell surface NA HNRNPU Heterogeneous nuclear ribonucleoprotein U (scaffold attachment factor A) Expressed in all Supported NA +Q02878 NX_Q02878 ENSG00000089009 288 32728 10.59 0 PE1 12 Cytoskeleton;Cytoskeleton NA RPL6 Ribosomal protein L6 Expressed in all Approved NA +Q08211 NX_Q08211 ENSG00000135829 1270 140958 6.41 0 PE1 1 Nucleus;Nucleolus;Cytoplasm NA DHX9 DEAH (Asp-Glu-Ala-His) box helicase 9 Expressed in all Supported NA +Q0VAA2 NX_Q0VAA2 ENSG00000100565 488 54535 5.22 0 PE1 14 NA NA LRRC74A Leucine rich repeat containing 74A Tissue enriched Uncertain testis: 7.0 +Q14093 NX_Q14093 ENSG00000155833 348 39079 9.74 0 PE1 9 Calyx NA CYLC2 Cylicin, basic protein of sperm head cytoskeleton 2 Tissue enriched NA testis: 79.9 +Q14393 NX_Q14393 ENSG00000183087 721 79677 5.84 0 PE1 13 Cytoplasm;Microtubule organizing center;Secreted NA GAS6 Growth arrest-specific 6 Expressed in all Approved NA +Q14693 NX_Q14693 ENSG00000134324 890 98664 6.14 0 PE1 2 Nucleus membrane;Cytosol;Endoplasmic reticulum membrane Myoglobinuria, acute recurrent, autosomal recessive LPIN1 Lipin 1 Expressed in all Approved NA +Q15393 NX_Q15393 ENSG00000189091 1217 135577 5.13 0 PE1 16 Nucleus;Nucleus;Nucleolus NA SF3B3 Splicing factor 3b, subunit 3, 130kDa Expressed in all Supported NA +Q2TAA8 NX_Q2TAA8 ENSG00000102904 658 76773 4.99 0 PE1 16 Perinuclear region NA TSNAXIP1 Translin-associated factor X interacting protein 1 Group enriched NA fallopian tube: 15.4;testis: 40.0 +Q494V2 NX_Q494V2 ENSG00000163885 611 71117 6.65 0 PE1 3 Cilium axoneme NA CFAP100 Cilia and flagella associated protein 100 Group enriched Approved fallopian tube: 43.0;testis: 34.3 +Q4G0X9 NX_Q4G0X9 ENSG00000141519 1142 130113 5.21 0 PE1 17 Cytoskeleton;Cytoplasm;Cilium Ciliary dyskinesia, primary, 15 CCDC40 Coiled-coil domain containing 40 Tissue enhanced Uncertain fallopian tube: 23.5 +Q502W7 NX_Q502W7 ENSG00000165972 563 65315 8.81 0 PE1 12 Centrosome NA CCDC38 Coiled-coil domain containing 38 Tissue enriched NA testis: 26.2 +Q53EV4 NX_Q53EV4 ENSG00000010626 343 39761 4.57 0 PE1 12 Nucleolus NA LRRC23 Leucine rich repeat containing 23 Group enriched Supported fallopian tube: 164.7;testis: 43.2 +Q53TS8 NX_Q53TS8 ENSG00000155754 623 71159 6.55 0 PE1 2 NA NA ALS2CR11 Amyotrophic lateral sclerosis 2 (juvenile) chromosome region, candidate 11 Tissue enriched NA testis: 73.8 +Q5BJF6 NX_Q5BJF6 ENSG00000136811 829 95401 7.53 0 PE1 9 Centrosome;Cilium;Centriole;Spindle pole;Centrosome NA ODF2 Outer dense fiber of sperm tails 2 Tissue enriched Supported testis: 533.7 +Q5I0G3 NX_Q5I0G3 ENSG00000138400 518 58651 5.85 0 PE1 2 NA NA MDH1B Malate dehydrogenase 1B, NAD (soluble) Group enriched Uncertain fallopian tube: 34.9;testis: 43.5 +Q5JU00 NX_Q5JU00 ENSG00000146221 501 55632 6.31 0 PE1 6 NA NA TCTE1 T-complex-associated-testis-expressed 1 Group enriched Uncertain fallopian tube: 22.8;testis: 35.3 +Q5JU67 NX_Q5JU67 ENSG00000160401 520 60533 8.88 0 PE1 9 Cytoplasmic vesicle;Cilium;Cell membrane;Cytoplasm NA CFAP157 Cilia and flagella associated protein 157 Tissue enriched Supported fallopian tube: 93.9 +Q5JX69 NX_Q5JX69 ENSG00000213714 171 19499 9.08 1 PE1 20 Membrane NA FAM209B Family with sequence similarity 209, member B Tissue enriched Supported testis: 111.9 +Q5T0N1 NX_Q5T0N1 ENSG00000156042 1121 125721 5.57 0 PE1 10 Cilium NA CFAP70 Cilia and flagella associated protein 70 Tissue enhanced Approved fallopian tube: 23.4;testis: 38.3 +Q5T1B0 NX_Q5T1B0 ENSG00000162779 1012 118027 5.49 0 PE1 1 NA NA AXDND1 Axonemal dynein light chain domain containing 1 Tissue enriched Supported testis: 24.4 +Q5T655 NX_Q5T655 ENSG00000120051 872 103417 8.44 0 PE1 10 Nucleus;Cilium NA CFAP58 Cilia and flagella associated protein 58 Group enriched Uncertain fallopian tube: 13.2;testis: 23.4 +Q5TCS8 NX_Q5TCS8 ENSG00000155085 1911 221413 4.96 0 PE1 6 Nucleus membrane;Nucleus;Cytoplasm;Nucleus NA AK9 Adenylate kinase 9 Tissue enhanced Approved testis: 31.1 +Q5TEZ5 NX_Q5TEZ5 ENSG00000203872 329 38553 6.49 0 PE1 6 NA NA C6orf163 Chromosome 6 open reading frame 163 Tissue enriched Uncertain testis: 13.9 +Q5TZF3 NX_Q5TZF3 ENSG00000183831 282 31810 4.59 0 PE1 1 NA NA ANKRD45 Ankyrin repeat domain 45 Tissue enhanced Supported fallopian tube: 34.5;parathyroid gland: 22.5;testis: 36.2 +Q5VTH9 NX_Q5VTH9 ENSG00000152763 848 94573 5.53 0 PE1 1 NA NA WDR78 WD repeat domain 78 Group enriched Uncertain fallopian tube: 43.2;testis: 62.6 +Q5VTT2 NX_Q5VTT2 ENSG00000204711 229 26445 6.75 1 PE1 9 Membrane NA C9orf135 Chromosome 9 open reading frame 135 Group enriched Uncertain fallopian tube: 54.5;testis: 24.2 +Q66K79 NX_Q66K79 ENSG00000109625 652 73655 8.22 0 PE1 4 Extracellular matrix NA CPZ Carboxypeptidase Z Tissue enhanced NA ovary: 121.2 +Q6NXR0 NX_Q6NXR0 ENSG00000124449 463 50288 5.22 0 PE1 19 NA NA IRGC Immunity-related GTPase family, cinema Tissue enriched Supported testis: 62.9 +Q6PF18 NX_Q6PF18 ENSG00000139714 240 27585 8.63 0 PE1 12 Nucleoplasm NA MORN3 MORN repeat containing 3 Tissue enhanced Uncertain fallopian tube: 6.7 +Q6URK8 NX_Q6URK8 ENSG00000159648 271 30717 9.09 0 PE1 16 Secreted NA TEPP Testis, prostate and placenta expressed Tissue enriched Supported testis: 7.3 +Q6XZB0 NX_Q6XZB0 ENSG00000188992 460 52992 9.22 0 PE1 21 Membrane;Secreted;Membrane Hypertriglyceridemia, familial LIPI Lipase, member I Tissue enriched NA epididymis: 568.5 +Q6ZNM6 NX_Q6ZNM6 ENSG00000196900 134 15452 9.3 0 PE1 5 NA NA TEX43 Testis expressed 43 Tissue enriched NA testis: 35.2 +Q75WM6 NX_Q75WM6 ENSG00000187166 255 28116 11.77 0 PE1 12 Nucleus;Chromosome NA H1FNT H1 histone family, member N, testis-specific Tissue enriched Approved testis: 77.7 +Q7Z304 NX_Q7Z304 ENSG00000165072 686 77556 5.05 0 PE1 9 Endoplasmic reticulum;Extracellular matrix NA MAMDC2 MAM domain containing 2 Mixed Uncertain NA +Q7Z4T9 NX_Q7Z4T9 ENSG00000183833 603 70999 7.34 0 PE1 3 Cytoplasm;Mitochondrion;Cilium axoneme;Mitochondrion NA MAATS1 MYCBP-associated, testis expressed 1 Tissue enhanced NA fallopian tube: 22.4;testis: 15.8 +Q7Z5J8 NX_Q7Z5J8 ENSG00000151687 1434 162026 8.39 1 PE1 2 Microtubule organizing center;Nucleus;Membrane NA ANKAR Ankyrin and armadillo repeat containing Tissue enriched Uncertain testis: 10.2 +Q7Z5V6 NX_Q7Z5V6 ENSG00000162148 425 47295 8.74 0 PE1 11 NA NA PPP1R32 Protein phosphatase 1, regulatory subunit 32 Tissue enhanced Supported fallopian tube: 64.0;testis: 87.4 +Q7Z7H3 NX_Q7Z7H3 ENSG00000158428 387 43900 5.28 0 PE1 2 Nucleus;Cytoplasm;Cell membrane;Cytoskeleton NA CATIP Ciliogenesis associated TTC17 interacting protein Tissue enhanced Supported fallopian tube: 31.6 +Q86UC2 NX_Q86UC2 ENSG00000130363 560 63687 5.53 0 PE1 6 Cytoplasmic vesicle;Cell membrane;Cilium axoneme;Cytoplasm Ciliary dyskinesia, primary, 32 RSPH3 Radial spoke 3 homolog (Chlamydomonas) Mixed Approved NA +Q86WT1 NX_Q86WT1 ENSG00000197557 665 76136 5.11 0 PE1 2 Cilium NA TTC30A Tetratricopeptide repeat domain 30A Mixed Supported NA +Q86WT6 NX_Q86WT6 ENSG00000185880; ENSG00000278211 500 57419 6.04 0 PE1 15 Cytoplasm;Nucleus;Nucleus speckle NA TRIM69 Tripartite motif containing 69 Tissue enriched Supported testis: 56.8 +Q86XH1 NX_Q86XH1 ENSG00000132321 822 95341 9.48 0 PE1 2 Nucleus NA IQCA1 IQ motif containing with AAA domain 1 Tissue enhanced NA fallopian tube: 17.7;thyroid gland: 32.1 +Q86XQ3 NX_Q86XQ3 ENSG00000152705 398 46422 5.88 6 PE1 5 Flagellum membrane NA CATSPER3 Cation channel, sperm associated 3 Tissue enriched NA testis: 38.3 +Q8IV63 NX_Q8IV63 ENSG00000105053 474 52881 9.21 0 PE1 19 Nucleus;Cytoplasmic vesicle;Nucleolus;Nucleus NA VRK3 Vaccinia related kinase 3 Expressed in all Approved NA +Q8IWZ5 NX_Q8IWZ5 ENSG00000155890 723 82745 8.3 0 PE1 3 NA NA TRIM42 Tripartite motif containing 42 Tissue enriched NA testis: 29.1 +Q8IXS2 NX_Q8IXS2 ENSG00000139537 484 57297 6.96 0 PE1 12 NA Ciliary dyskinesia, primary, 27 CCDC65 Coiled-coil domain containing 65 Group enriched Uncertain fallopian tube: 42.4;testis: 67.5 +Q8IY82 NX_Q8IY82 ENSG00000159625 874 103497 5.49 0 PE1 16 Flagellum;Cilium axoneme NA DRC7 Dynein regulatory complex subunit 7 Group enriched Uncertain fallopian tube: 32.4;testis: 81.1 +Q8IYE0 NX_Q8IYE0 ENSG00000135205 955 112806 8.59 0 PE1 7 Centriole NA CCDC146 Coiled-coil domain containing 146 Tissue enhanced Uncertain fallopian tube: 57.0;testis: 39.7 +Q8IYM1 NX_Q8IYM1 ENSG00000140623 358 40748 6.67 0 PE1 16 Cytoplasm;Cytoskeleton;Spindle;Nucleus;Flagellum Spermatogenic failure 10 SEPT12 Septin 12 Tissue enriched NA testis: 107.9 +Q8IYR0 NX_Q8IYR0 ENSG00000272514 622 71193 6.38 0 PE1 6 Cilium axoneme NA CFAP206 Cilia and flagella associated protein 206 Group enriched Approved fallopian tube: 35.3;testis: 107.4 +Q8IYW2 NX_Q8IYW2 ENSG00000171811 2715 303500 7.07 0 PE1 10 Cilium axoneme NA CFAP46 Cilia and flagella associated protein 46 Tissue enhanced Uncertain fallopian tube: 8.4;testis: 17.6 +Q8N443 NX_Q8N443 ENSG00000158423 379 44015 8.92 0 PE1 X NA NA RIBC1 RIB43A domain with coiled-coils 1 Group enriched Uncertain fallopian tube: 44.6;testis: 41.6 +Q8N865 NX_Q8N865 ENSG00000153790 590 68464 6.9 0 PE1 7 Centrosome NA C7orf31 Chromosome 7 open reading frame 31 Tissue enriched NA testis: 130.7 +Q8NA54 NX_Q8NA54 ENSG00000164675 791 92581 6.21 0 PE1 7 NA NA IQUB IQ motif and ubiquitin domain containing Tissue enriched NA testis: 65.9 +Q8NA56 NX_Q8NA56 ENSG00000137473 475 55082 5.5 0 PE1 4 NA NA TTC29 Tetratricopeptide repeat domain 29 Group enriched Uncertain fallopian tube: 33.8;testis: 150.4 +Q8NAT1 NX_Q8NAT1 ENSG00000144647 580 66615 8.81 1 PE1 3 Endoplasmic reticulum membrane Muscular dystrophy-dystroglycanopathy congenital with brain and eye anomalies A8 POMGNT2 Protein O-linked mannose N-acetylglucosaminyltransferase 2 (beta 1,4-) Expressed in all Uncertain NA +Q8NBM4 NX_Q8NBM4 ENSG00000134882 344 38964 9.21 3 PE1 13 Cytoplasm;Endoplasmic reticulum membrane NA UBAC2 UBA domain containing 2 Expressed in all Approved NA +Q8NBZ7 NX_Q8NBZ7 ENSG00000115652 420 47577 8.99 1 PE1 2 Golgi stack membrane NA UXS1 UDP-glucuronate decarboxylase 1 Expressed in all Uncertain NA +Q8NCR6 NX_Q8NCR6 ENSG00000164972 262 30167 8.76 0 PE1 9 Cytoskeleton;Nucleus;Cytoplasm NA C9orf24 Chromosome 9 open reading frame 24 Group enriched Uncertain fallopian tube: 172.5;testis: 65.1 +Q8ND07 NX_Q8ND07 ENSG00000119636 529 61987 9.07 0 PE1 14 Microtubule organizing center;Nucleus;Cell membrane;Cilium basal body NA BBOF1 Basal body orientation factor 1 Tissue enhanced Uncertain testis: 69.7 +Q8NDM7 NX_Q8NDM7 ENSG00000197748 1665 191984 5.71 0 PE1 10 Cytoplasm;Nucleus;Flagellum NA CFAP43 Cilia and flagella associated protein 43 Group enriched NA fallopian tube: 77.1;testis: 102.7 +Q8NE09 NX_Q8NE09 ENSG00000132554 1264 147163 8.08 0 PE1 8 Cytoplasm;Nucleus NA RGS22 Regulator of G-protein signaling 22 Tissue enriched NA testis: 108.4 +Q8NEC5 NX_Q8NEC5 ENSG00000175294 780 90091 7.22 6 PE1 11 Flagellum membrane Spermatogenic failure 7 CATSPER1 Cation channel, sperm associated 1 Tissue enriched NA testis: 20.4 +Q8NEY3 NX_Q8NEY3 ENSG00000150628 305 34751 9.86 0 PE1 4 NA NA SPATA4 Spermatogenesis associated 4 Tissue enriched Supported testis: 241.7 +Q8NHU2 NX_Q8NHU2 ENSG00000089101 1237 141349 5.76 0 PE1 20 Cytoplasm;Nucleoplasm;Cilium axoneme NA CFAP61 Cilia and flagella associated protein 61 Group enriched Uncertain fallopian tube: 20.0;heart muscle: 6.9;testis: 30.1 +Q8TBZ2 NX_Q8TBZ2 ENSG00000136449 947 108153 7.13 0 PE1 17 Cytoplasm;Membrane NA MYCBPAP MYCBP associated protein Tissue enriched Supported testis: 91.0 +Q8TC36 NX_Q8TC36 ENSG00000167098 379 43081 8.61 1 PE1 20 Nucleus inner membrane NA SUN5 Sad1 and UNC84 domain containing 5 Tissue enriched Supported testis: 40.8 +Q8TC94 NX_Q8TC94 ENSG00000181786 416 45627 6.61 0 PE1 19 Cytoskeleton NA ACTL9 Actin-like 9 Tissue enriched Uncertain testis: 50.2 +Q8TC99 NX_Q8TC99 ENSG00000073598 324 35921 5.01 0 PE1 17 NA NA FNDC8 Fibronectin type III domain containing 8 Tissue enriched Supported testis: 107.9 +Q8WW14 NX_Q8WW14 ENSG00000165863 230 25923 8.78 0 PE1 10 Mitochondrion NA C10orf82 Chromosome 10 open reading frame 82 Tissue enriched NA testis: 111.2 +Q8WW24 NX_Q8WW24 ENSG00000163060 435 50649 6.01 0 PE1 2 Flagellum;Flagellum axoneme;Cilium axoneme NA TEKT4 Tektin 4 Group enriched Uncertain fallopian tube: 4.2;testis: 5.2 +Q8WYA0 NX_Q8WYA0 ENSG00000122970 676 79746 8.9 0 PE1 12 Cytoplasm;Centrosome;Cilium NA IFT81 Intraflagellar transport 81 Mixed Supported NA +Q8WYR4 NX_Q8WYR4 ENSG00000160188 309 35124 4.58 0 PE1 21 Nucleoplasm;Cytoplasm;Cilium Ciliary dyskinesia, primary, 24 RSPH1 Radial spoke head 1 homolog (Chlamydomonas) Tissue enriched Supported fallopian tube: 249.5 +Q92743 NX_Q92743 ENSG00000166033 480 51287 8.09 0 PE1 10 Cell membrane;Cell membrane;Secreted;Cytosol Cerebral arteriopathy, autosomal dominant, with subcortical infarcts and leukoencephalopathy, 2;Macular degeneration, age-related, 7;Cerebral arteriopathy, autosomal recessive, with subcortical infarcts and leukoencephalopathy HTRA1 HtrA serine peptidase 1 Mixed Approved NA +Q969V4 NX_Q969V4 ENSG00000167858 418 48283 5.98 0 PE1 17 Cilium axoneme;Flagellum axoneme NA TEKT1 Tektin 1 Group enriched Supported fallopian tube: 79.4;testis: 18.3 +Q96DB2 NX_Q96DB2 ENSG00000163517 347 39183 7.17 0 PE1 3 Cell membrane;Nucleus NA HDAC11 Histone deacetylase 11 Mixed NA NA +Q96DY2 NX_Q96DY2 ENSG00000166578 449 52359 9.26 0 PE1 12 NA NA IQCD IQ motif containing D Group enriched Uncertain fallopian tube: 34.5;testis: 65.3 +Q96EY1 NX_Q96EY1 ENSG00000103423; ENSG00000276726 480 52489 9.37 0 PE1 16 Mitochondrion matrix;Mitochondrion;Cytosol;Postsynaptic cell membrane NA DNAJA3 DnaJ (Hsp40) homolog, subfamily A, member 3 Expressed in all Approved NA +Q96LB3 NX_Q96LB3 ENSG00000096872 600 69239 5.73 0 PE1 9 Golgi apparatus;Cilium;Cytoplasmic vesicle Bardet-Biedl syndrome 20 IFT74 Intraflagellar transport 74 Expressed in all Approved NA +Q96LI6 NX_Q96LI6 ENSG00000169953; ENSG00000172468 401 45107 6.68 0 PE1 Y Nucleus;Cytoplasm NA HSFY2 Heat shock transcription factor, Y-linked 2 Tissue enriched NA testis: 24.5 +Q96LK8 NX_Q96LK8 ENSG00000184361 384 42325 4.7 0 PE1 17 NA NA SPATA32 Spermatogenesis associated 32 Tissue enriched Uncertain testis: 40.8 +Q96M29 NX_Q96M29 ENSG00000153060 485 56294 6.8 0 PE1 16 Flagellum NA TEKT5 Tektin 5 Tissue enriched NA testis: 45.4 +Q96M32 NX_Q96M32 ENSG00000140057 723 82658 4.67 0 PE1 14 Cytoplasm;Cytosol;Nucleus NA AK7 Adenylate kinase 7 Tissue enhanced Approved fallopian tube: 38.5 +Q96M63 NX_Q96M63 ENSG00000105479 670 75046 5.87 0 PE1 19 Cilium Ciliary dyskinesia, primary, 20 CCDC114 Coiled-coil domain containing 114 Group enriched Approved fallopian tube: 6.5;testis: 5.8 +Q96M69 NX_Q96M69 ENSG00000155530 825 93618 6 0 PE1 7 Acrosome NA LRGUK Leucine-rich repeats and guanylate kinase domain containing Group enriched Uncertain epididymis: 1.7;fallopian tube: 5.4;testis: 8.3 +Q96M86 NX_Q96M86 ENSG00000179532 4753 533644 6.25 0 PE1 11 Nucleoplasm NA DNHD1 Dynein heavy chain domain 1 Tissue enriched Uncertain testis: 19.5 +Q96M91 NX_Q96M91 ENSG00000172361 514 61835 9 0 PE1 18 Cilium Heterotaxy, visceral, 6, autosomal CFAP53 Cilia and flagella associated protein 53 Group enriched Supported fallopian tube: 44.1;testis: 126.4 +Q96M95 NX_Q96M95 ENSG00000161973 316 38019 9.18 0 PE1 17 NA NA CCDC42 Coiled-coil domain containing 42 Tissue enriched NA testis: 128.7 +Q96MA6 NX_Q96MA6 ENSG00000165695 479 54926 5.77 0 PE1 9 Cytosol NA AK8 Adenylate kinase 8 Tissue enhanced Approved fallopian tube: 29.6;testis: 21.6 +Q96MC2 NX_Q96MC2 ENSG00000157856 740 87134 5.3 0 PE1 2 Cilium axoneme Ciliary dyskinesia, primary, 21 DRC1 Dynein regulatory complex subunit 1 Group enriched NA fallopian tube: 61.8;testis: 36.7 +Q96MR6 NX_Q96MR6 ENSG00000243710 1250 144961 5.61 0 PE1 1 Cytoplasm NA CFAP57 Cilia and flagella associated protein 57 Group enriched Supported fallopian tube: 35.3;testis: 27.6 +Q96MT7 NX_Q96MT7 ENSG00000206530 982 111729 4.75 0 PE1 3 Flagellum NA CFAP44 Cilia and flagella associated protein 44 Tissue enhanced Uncertain testis: 24.9 +Q96N23 NX_Q96N23 ENSG00000188596 3096 351970 8.41 0 PE1 12 Cilium axoneme NA CFAP54 Cilia and flagella associated 54 Mixed Supported NA +Q96P26 NX_Q96P26 ENSG00000185013 610 68804 9.03 0 PE1 2 Cytoplasm NA NT5C1B 5'-nucleotidase, cytosolic IB Tissue enriched Uncertain testis: 57.8 +Q96PF2 NX_Q96PF2 ENSG00000206203 358 40939 9.02 0 PE1 22 Cytoplasm;Centriole NA TSSK2 Testis-specific serine kinase 2 Tissue enriched NA testis: 120.0 +Q96RN1 NX_Q96RN1 ENSG00000112053 970 109006 5.86 12 PE1 6 Membrane Spermatogenic failure 3 SLC26A8 Solute carrier family 26 (anion exchanger), member 8 Tissue enriched Uncertain testis: 75.6 +Q96SB4 NX_Q96SB4 ENSG00000096063 655 74325 5.81 0 PE1 6 Cytoplasm;Cytoplasm;Nucleus;Nucleus;Cell membrane;Cytoplasm;Nucleus;Nucleus matrix;Microsome;Cytoplasm;Nucleus matrix;Microsome NA SRPK1 SRSF protein kinase 1 Expressed in all Approved NA +Q99932 NX_Q99932 ENSG00000137098 426 44819 5.31 0 PE1 9 Cytoplasm;Nucleus;Acrosome;Microtubule organizing center;Spindle NA SPAG8 Sperm associated antigen 8 Group enriched Supported fallopian tube: 28.7;testis: 16.3 +Q9BRK5 NX_Q9BRK5 ENSG00000078808 362 41807 4.76 0 PE1 1 Golgi apparatus;Bleb;Golgi apparatus lumen;Cytoplasm;Cell membrane NA SDF4 Stromal cell derived factor 4 Expressed in all Supported NA +Q9BRQ6 NX_Q9BRQ6 ENSG00000159685 235 26458 9.01 0 PE1 3 Cytoplasm;Nucleus;Mitochondrion;Mitochondrion inner membrane;Mitochondrion NA CHCHD6 Coiled-coil-helix-coiled-coil-helix domain containing 6 Expressed in all Approved NA +Q9BXA6 NX_Q9BXA6 ENSG00000178093 273 30331 9.24 0 PE1 19 NA NA TSSK6 Testis-specific serine kinase 6 Tissue enriched NA testis: 18.7 +Q9BXC9 NX_Q9BXC9 ENSG00000125124 721 79871 5.74 0 PE1 16 Cilium membrane;Cytoplasm;Centriolar satellite Bardet-Biedl syndrome 2;Retinitis pigmentosa 74 BBS2 Bardet-Biedl syndrome 2 Expressed in all Approved NA +Q9BXF9 NX_Q9BXF9 ENSG00000125409 490 56636 6.93 0 PE1 17 Cilium axoneme;Flagellum axoneme NA TEKT3 Tektin 3 Tissue enriched Uncertain testis: 46.0 +Q9BY76 NX_Q9BY76 ENSG00000167772 406 45214 9.07 0 PE1 19 Secreted;Extracellular matrix NA ANGPTL4 Angiopoietin-like 4 Tissue enhanced Approved adipose tissue: 78.2 +Q9BZW7 NX_Q9BZW7 ENSG00000135951 698 81421 5.73 0 PE1 2 Nucleus;Cytoplasm;Cytoplasm;Nucleus;Nucleus membrane NA TSGA10 Testis specific, 10 Group enriched Approved fallopian tube: 19.0;testis: 92.4 +Q9C0B2 NX_Q9C0B2 ENSG00000142609 1584 178589 6.01 0 PE1 1 Cilium axoneme NA CFAP74 Cilia and flagella associated protein 74 Tissue enhanced Supported fallopian tube: 10.4;testis: 9.0 +Q9H069 NX_Q9H069 ENSG00000171962 523 61054 4.68 0 PE1 17 Cytoplasm;Cilium axoneme NA DRC3 Dynein regulatory complex subunit 3 Tissue enhanced Approved fallopian tube: 98.0 +Q9H095 NX_Q9H095 ENSG00000114473 443 51918 6.18 0 PE1 3 Cytoplasm;Cytoskeleton;Cytoplasm;Flagellum;Cilium;Cytoskeleton NA IQCG IQ motif containing G Group enriched NA fallopian tube: 83.0;testis: 78.7 +Q9H0C1 NX_Q9H0C1 ENSG00000066185 365 41818 5.82 0 PE1 1 Nucleus;Cytoplasm NA ZMYND12 Zinc finger, MYND-type containing 12 Tissue enhanced NA fallopian tube: 23.1;testis: 51.6 +Q9H0I3 NX_Q9H0I3 ENSG00000103021 377 44220 8.75 0 PE1 16 Nucleus;Cytoplasm;Cytoplasm;Nucleoplasm;Centriolar satellite NA CCDC113 Coiled-coil domain containing 113 Tissue enhanced Uncertain fallopian tube: 49.6;testis: 32.7 +Q9H0K4 NX_Q9H0K4 ENSG00000104941 717 80913 4.36 0 PE1 19 Nucleus;Cytoplasm NA RSPH6A Radial spoke head 6 homolog A (Chlamydomonas) Tissue enriched Approved testis: 30.5 +Q9H1X1 NX_Q9H1X1 ENSG00000172426 276 31292 5.28 0 PE1 6 Cilium axoneme Ciliary dyskinesia, primary, 12 RSPH9 Radial spoke head 9 homolog (Chlamydomonas) Group enriched Supported fallopian tube: 14.5;testis: 12.6 +Q9H4K1 NX_Q9H4K1 ENSG00000128408 309 37060 9.57 0 PE1 22 NA NA RIBC2 RIB43A domain with coiled-coils 2 Group enriched Uncertain fallopian tube: 15.8;testis: 37.3 +Q9HBG6 NX_Q9HBG6 ENSG00000163913 1241 141825 6.08 0 PE1 3 Cytoplasm;Nucleoplasm;Cytoplasm;Cilium;Cilium basal body Cranioectodermal dysplasia 1 IFT122 Intraflagellar transport 122 Expressed in all Approved NA +Q9HCU5 NX_Q9HCU5 ENSG00000138073 417 45468 8.02 1 PE1 2 Endoplasmic reticulum;Endoplasmic reticulum membrane;Nucleus NA PREB Prolactin regulatory element binding Expressed in all Uncertain NA +Q9NR50 NX_Q9NR50 ENSG00000070785 452 50240 6.08 0 PE1 1 Cytoplasm;Cytoplasmic vesicle;Cytoplasm Leukodystrophy with vanishing white matter EIF2B3 Eukaryotic translation initiation factor 2B, subunit 3 gamma, 58kDa Expressed in all Supported NA +Q9NU02 NX_Q9NU02 ENSG00000132623 776 86664 8.51 0 PE1 20 NA NA ANKEF1 Ankyrin repeat and EF-hand domain containing 1 Tissue enhanced Approved testis: 33.7 +Q9NVH1 NX_Q9NVH1 ENSG00000007923 559 63278 8.54 0 PE1 1 Cytoplasm;Mitochondrion NA DNAJC11 DnaJ (Hsp40) homolog, subfamily C, member 11 Expressed in all Uncertain NA +Q9NWB7 NX_Q9NWB7 ENSG00000114446 429 49108 4.93 0 PE1 3 Cilium basal body NA IFT57 Intraflagellar transport 57 Mixed Supported NA +Q9P0V9 NX_Q9P0V9 ENSG00000186522 454 52593 6.35 0 PE1 2 Cytoplasm;Cell membrane;Cytoskeleton;Cytoskeleton;Cytoplasm;Cytoskeleton NA SEPT10 Septin 10 Mixed Approved NA +Q9P1Z9 NX_Q9P1Z9 ENSG00000197816 1646 191100 5.74 1 PE1 9 Membrane NA CCDC180 Coiled-coil domain containing 180 Group enriched NA fallopian tube: 15.6;testis: 37.7 +Q9P2H3 NX_Q9P2H3 ENSG00000068885 777 88035 7.59 0 PE1 3 Cytoplasm;Cilium basal body;Cilium axoneme Short-rib thoracic dysplasia 2 with or without polydactyly IFT80 Intraflagellar transport 80 Expressed in all Uncertain NA +Q9P2M1 NX_Q9P2M1 ENSG00000109771 347 39780 7.99 0 PE1 4 Cytoplasm NA LRP2BP LRP2 binding protein Tissue enhanced Approved fallopian tube: 12.5;testis: 20.2 +Q9P2S6 NX_Q9P2S6 ENSG00000144504 941 105516 6.28 0 PE1 2 Cytoplasm;Cytoplasm;Nucleus NA ANKMY1 Ankyrin repeat and MYND domain containing 1 Group enriched Uncertain fallopian tube: 39.0;testis: 118.1 +Q9UFE4 NX_Q9UFE4 ENSG00000145075 941 109901 6.1 0 PE1 3 Mitochondrion;Cilium axoneme Ciliary dyskinesia, primary, 14 CCDC39 Coiled-coil domain containing 39 Mixed Supported NA +Q9UHP6 NX_Q9UHP6 ENSG00000100218 348 38592 6.43 0 PE1 22 NA NA RSPH14 Radial spoke head 14 homolog (Chlamydomonas) Tissue enhanced Uncertain fallopian tube: 18.8;testis: 30.8 +Q9UI46 NX_Q9UI46 ENSG00000122735 699 79283 6.4 0 PE1 9 Cilium axoneme Ciliary dyskinesia, primary, 1;Kartagener syndrome DNAI1 Dynein, axonemal, intermediate chain 1 Group enriched Approved fallopian tube: 53.6;testis: 60.9 +Q9UIF3 NX_Q9UIF3 ENSG00000092850 430 49672 5.39 0 PE1 1 Flagellum;Cilium axoneme;Flagellum axoneme NA TEKT2 Tektin 2 (testicular) Group enriched Approved fallopian tube: 96.6;testis: 63.3 +Q9Y238 NX_Q9Y238 ENSG00000008226 1755 195684 5.92 0 PE1 3 Cytoplasm Lung cancer;Esophageal cancer DLEC1 Deleted in lung and esophageal cancer 1 Tissue enhanced Supported fallopian tube: 29.4;testis: 17.3 +Q9Y366 NX_Q9Y366 ENSG00000101052 437 49706 5.14 0 PE1 20 Cytoplasm;Cilium Short-rib thoracic dysplasia 16 with or without polydactyly IFT52 Intraflagellar transport 52 Expressed in all Supported NA +Q9Y4P3 NX_Q9Y4P3 ENSG00000106638 447 49798 9.52 0 PE1 7 Cytoplasm NA TBL2 Transducin (beta)-like 2 Tissue enriched NA testis: 83.4 +Q9Y512 NX_Q9Y512 ENSG00000100347 469 51976 6.44 0 PE1 22 Mitochondrion;Mitochondrion outer membrane;Cytoplasm;Mitochondrion NA SAMM50 SAMM50 sorting and assembly machinery component Expressed in all Supported NA +Q9Y678 NX_Q9Y678 ENSG00000181789 874 97718 5.32 0 PE1 3 Golgi apparatus;Cytoplasm;Golgi apparatus membrane;COPI-coated vesicle membrane NA COPG1 Coatomer protein complex, subunit gamma 1 Expressed in all Supported NA +Q9Y6J8 NX_Q9Y6J8 ENSG00000127952 313 35818 5.73 0 PE1 7 NA NA STYXL1 Serine/threonine/tyrosine interacting-like 1 Expressed in all Uncertain NA
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/input_test.txt Tue Dec 18 09:21:32 2018 -0500 @@ -0,0 +1,142 @@ +Protein accession number (UniProt) Protein name Number of peptides (razor + unique) Ensembl Gene Gene description RNA tissue category RNA TS TPM +P15924 Desmoplakin 69 ENSG00000096696 DSP Desmoplakin Group enriched esophagus: 346.9;skin: 1019.0 +P02538 Keratin, type II cytoskeletal 6A 53 ENSG00000205420 KRT6A Keratin 6A, type II Tissue enriched esophagus: 5726.3 +P02768 Serum albumin 44 ENSG00000163631 ALB Albumin Tissue enriched liver: 105632.0 +P08779 Keratin, type I cytoskeletal 16 29 ENSG00000186832 KRT16 Keratin 16, type I Group enriched esophagus: 479.6;tonsil: 106.5 +Q02413 Desmoglein-1 24 ENSG00000134760 DSG1 Desmoglein 1 Tissue enriched skin: 727.4 +P07355 Annexin A2;Putative annexin A2-like protein 22 ENSG00000182718 ANXA2 Annexin A2 Expressed in all NA +P14923 Junction plakoglobin 22 ENSG00000173801 JUP Junction plakoglobin Group enriched esophagus: 493.6;skin: 787.3 +P02788 Lactotransferrin 21 ENSG00000012223 LTF Lactotransferrin Tissue enhanced bone marrow: 2808.6;cervix, uterine: 1024.2 +Q9HC84 Mucin-5B 21 ENSG00000117983 MUC5B Mucin 5B, oligomeric mucus/gel-forming Group enriched cervix, uterine: 347.7;gallbladder: 346.8 +P29508 Serpin B3 20 ENSG00000057149 SERPINB3 Serpin peptidase inhibitor, clade B (ovalbumin), member 3 Group enriched cervix, uterine: 297.6;esophagus: 851.2 +P63261 Actin, cytoplasmic 2 19 ENSG00000184009 ACTG1 Actin gamma 1 Expressed in all NA +Q8N1N4 Keratin, type II cytoskeletal 78 18 ENSG00000170423 KRT78 Keratin 78, type II Tissue enriched esophagus: 1058.9 +Q04695 Keratin, type I cytoskeletal 17 18 ENSG00000128422 KRT17 Keratin 17, type I Tissue enhanced breast: 219.7;seminal vesicle: 223.4;urinary bladder: 334.2 +P01876 Ig alpha-1 chain C region 16 ENSG00000211895; ENSG00000282633 NA NA NA NA +Q01469 Fatty acid-binding protein 5, epidermal 15 ENSG00000164687 FABP5 Fatty acid binding protein 5 (psoriasis-associated) Expressed in all NA +P31944 Caspase-14 15 ENSG00000105141 CASP14 Caspase 14, apoptosis-related cysteine peptidase Tissue enriched skin: 560.0 +P01833 Polymeric immunoglobulin receptor 15 ENSG00000162896 PIGR Polymeric immunoglobulin receptor Tissue enhanced colon: 1721.7;duodenum: 2732.8 +P06733 Alpha-enolase 15 ENSG00000074800 ENO1 Enolase 1, (alpha) Expressed in all NA +Q15149 Plectin 15 ENSG00000178209 PLEC Plectin Expressed in all NA +P19013 Keratin, type II cytoskeletal 4 13 ENSG00000170477 KRT4 Keratin 4, type II Tissue enriched esophagus: 14911.0 +Q6KB66 Keratin, type II cytoskeletal 80 13 ENSG00000167767 KRT80 Keratin 80, type II Tissue enhanced skin: 125.3 +Q08188 Protein-glutamine gamma-glutamyltransferase E 12 ENSG00000125780 TGM3 Transglutaminase 3 Tissue enriched esophagus: 1519.7 +P13646 Keratin, type I cytoskeletal 13 11 ENSG00000171401 KRT13 Keratin 13, type I Tissue enriched esophagus: 35268.3 +Q86YZ3 Hornerin 11 ENSG00000197915 HRNR Hornerin Not detected NA +P04259 Keratin, type II cytoskeletal 6B 10 ENSG00000185479 KRT6B Keratin 6B, type II Tissue enriched esophagus: 673.4 +P02545 Prelamin-A/C;Lamin-A/C 10 ENSG00000160789 LMNA Lamin A/C Expressed in all NA +P04083 Annexin A1 10 ENSG00000135046 ANXA1 Annexin A1 Tissue enriched esophagus: 7577.8 +P11021 78 kDa glucose-regulated protein 10 ENSG00000044574 HSPA5 Heat shock 70kDa protein 5 (glucose-regulated protein, 78kDa) Expressed in all NA +P02787 Serotransferrin 9 ENSG00000091513 TF Transferrin Tissue enriched liver: 5384.6 +P04040 Catalase 9 ENSG00000121691 CAT Catalase Expressed in all NA +P31151 Protein S100-A7 9 ENSG00000143556 S100A7 S100 calcium binding protein A7 Group enriched skin: 325.1;tonsil: 921.8 +P31947 14-3-3 protein sigma 9 ENSG00000175793 SFN Stratifin Group enriched esophagus: 1094.4;skin: 1158.9 +Q96P63 Serpin B12 9 ENSG00000166634 SERPINB12 Serpin peptidase inhibitor, clade B (ovalbumin), member 12 Tissue enriched skin: 78.4 +P14618 Pyruvate kinase PKM 9 ENSG00000067225 PKM Pyruvate kinase, muscle Expressed in all NA +P60174 Triosephosphate isomerase 9 ENSG00000111669 TPI1 Triosephosphate isomerase 1 Expressed in all NA +Q06830 Peroxiredoxin-1 9 ENSG00000117450 PRDX1 Peroxiredoxin 1 Expressed in all NA +P01040 Cystatin-A 8 ENSG00000121552 CSTA Cystatin A (stefin A) Group enriched esophagus: 3891.8;tonsil: 868.8 +P05089 Arginase-1 8 ENSG00000118520 ARG1 Arginase 1 Tissue enhanced bone marrow: 171.2;liver: 564.5 +P01834 Ig kappa chain C region 8 NA NA NA NA NA +P04406 Glyceraldehyde-3-phosphate dehydrogenase 8 ENSG00000111640 GAPDH Glyceraldehyde-3-phosphate dehydrogenase Expressed in all NA +P0DMV9 Heat shock 70 kDa protein 1B 8 ENSG00000204388; ENSG00000224501; ENSG00000212866; ENSG00000231555; ENSG00000232804 HSPA1B Heat shock 70kDa protein 1B Tissue enhanced adrenal gland: 34.3 +P13639 Elongation factor 2 8 ENSG00000167658 EEF2 Eukaryotic translation elongation factor 2 Expressed in all NA +P35579 Myosin-9 8 ENSG00000100345 MYH9 Myosin, heavy chain 9, non-muscle Expressed in all NA +P68371 Tubulin beta-4B chain 8 ENSG00000188229 TUBB4B Tubulin, beta 4B class IVb Expressed in all NA +Q8WVV4 Protein POF1B 8 ENSG00000124429 POF1B Premature ovarian failure, 1B Tissue enhanced skin: 144.8 +O75635 Serpin B7 7 ENSG00000166396 SERPINB7 Serpin peptidase inhibitor, clade B (ovalbumin), member 7 Tissue enhanced skin: 123.8;tonsil: 35.5 +P01857 Ig gamma-1 chain C region 7 ENSG00000211896; ENSG00000277633 NA NA NA NA +P61626 Lysozyme C 7 ENSG00000090382 LYZ Lysozyme Expressed in all NA +P68363 Tubulin alpha-1B chain 7 ENSG00000123416 TUBA1B Tubulin, alpha 1b Expressed in all NA +P01009 Alpha-1-antitrypsin;Short peptide from AAT 6 ENSG00000197249 SERPINA1 Serpin peptidase inhibitor, clade A (alpha-1 antiproteinase, antitrypsin), member 1 Tissue enriched liver: 15340.0 +P07900 Heat shock protein HSP 90-alpha 6 ENSG00000080824 HSP90AA1 Heat shock protein 90kDa alpha (cytosolic), class A member 1 Expressed in all NA +Q9NZH8 Interleukin-36 gamma 6 ENSG00000136688 IL36G Interleukin 36, gamma Group enriched skin: 15.8;tonsil: 40.8 +O43707 Alpha-actinin-4;Alpha-actinin-1 6 ENSG00000130402; ENSG00000282844 ACTN4 Actinin, alpha 4 Expressed in all NA +O75223 Gamma-glutamylcyclotransferase 6 ENSG00000006625 GGCT Gamma-glutamylcyclotransferase Expressed in all NA +P00338 L-lactate dehydrogenase A chain 6 ENSG00000134333 LDHA Lactate dehydrogenase A Expressed in all NA +P07339 Cathepsin D 6 ENSG00000117984 CTSD Cathepsin D Expressed in all NA +P62987 Ubiquitin-60S ribosomal protein L40 6 ENSG00000221983 UBA52 Ubiquitin A-52 residue ribosomal protein fusion product 1 Expressed in all NA +P10599 Thioredoxin 6 ENSG00000136810 TXN Thioredoxin Expressed in all NA +Q9UGM3 Deleted in malignant brain tumors 1 protein 6 ENSG00000187908 DMBT1 Deleted in malignant brain tumors 1 Tissue enhanced duodenum: 876.2;small intestine: 299.5 +Q9UI42 Carboxypeptidase A4 6 ENSG00000128510 CPA4 Carboxypeptidase A4 Tissue enriched skin: 68.0 +P47929 Galectin-7 5 ENSG00000178934; ENSG00000205076; ENSG00000282902; ENSG00000283082 LGALS7B Lectin, galactoside-binding, soluble, 7B Tissue enhanced breast: 10.2;esophagus: 19.4 +Q13867 Bleomycin hydrolase 5 ENSG00000108578 BLMH Bleomycin hydrolase Expressed in all NA +Q6P4A8 Phospholipase B-like 1 5 ENSG00000121316 PLBD1 Phospholipase B domain containing 1 Expressed in all NA +O75369 Filamin-B 5 ENSG00000136068 FLNB Filamin B, beta Expressed in all NA +P00441 Superoxide dismutase [Cu-Zn] 5 ENSG00000142168 SOD1 Superoxide dismutase 1, soluble Expressed in all NA +P04792 Heat shock protein beta-1 5 ENSG00000106211 HSPB1 Heat shock 27kDa protein 1 Expressed in all NA +P11142 Heat shock cognate 71 kDa protein 5 ENSG00000109971 HSPA8 Heat shock 70kDa protein 8 Expressed in all NA +P58107 Epiplakin 5 ENSG00000261150 EPPK1 Epiplakin 1 Tissue enhanced skin: 11.2 +P60842 Eukaryotic initiation factor 4A-I 5 ENSG00000161960 EIF4A1 Eukaryotic translation initiation factor 4A1 Expressed in all NA +P62937 Peptidyl-prolyl cis-trans isomerase A 5 ENSG00000196262 PPIA Peptidylprolyl isomerase A (cyclophilin A) Expressed in all NA +P63104 14-3-3 protein zeta/delta 5 ENSG00000164924 YWHAZ Tyrosine 3-monooxygenase/tryptophan 5-monooxygenase activation protein, zeta Expressed in all NA +Q92820 Gamma-glutamyl hydrolase 5 ENSG00000137563 GGH Gamma-glutamyl hydrolase (conjugase, folylpolygammaglutamyl hydrolase) Tissue enhanced kidney: 89.2 +O75342 Arachidonate 12-lipoxygenase, 12R-type 4 ENSG00000179477 ALOX12B Arachidonate 12-lipoxygenase, 12R type Group enriched skin: 70.1;tonsil: 18.1 +P09211 Glutathione S-transferase P 4 ENSG00000084207 GSTP1 Glutathione S-transferase pi 1 Expressed in all NA +P31025 Lipocalin-1 4 ENSG00000160349 LCN1 Lipocalin 1 Group enriched fallopian tube: 3.0;seminal vesicle: 12.1 +P48594 Serpin B4 4 ENSG00000206073 SERPINB4 Serpin peptidase inhibitor, clade B (ovalbumin), member 4 Group enriched esophagus: 98.6;urinary bladder: 20.1 +Q14574 Desmocollin-3 4 ENSG00000134762 DSC3 Desmocollin 3 Group enriched esophagus: 119.5;skin: 455.7 +Q5T750 Skin-specific protein 32 4 ENSG00000198854 C1orf68 Chromosome 1 open reading frame 68 Tissue enriched skin: 807.2 +Q6UWP8 Suprabasin 4 ENSG00000189001 SBSN Suprabasin Group enriched esophagus: 1059.9;skin: 2694.5 +O60911 Cathepsin L2 4 ENSG00000136943 CTSV Cathepsin V Tissue enhanced cervix, uterine: 68.9;skin: 64.3;testis: 131.2 +P00558 Phosphoglycerate kinase 1 4 ENSG00000102144 PGK1 Phosphoglycerate kinase 1 Expressed in all NA +P04075 Fructose-bisphosphate aldolase A 4 ENSG00000149925 ALDOA Aldolase A, fructose-bisphosphate Tissue enriched skeletal muscle: 9379.1 +P07384 Calpain-1 catalytic subunit 4 ENSG00000014216 CAPN1 Calpain 1, (mu/I) large subunit Expressed in all NA +P0CG05 Ig lambda-2 chain C regions 4 NA NA NA NA NA +P18206 Vinculin 4 ENSG00000035403 VCL Vinculin Expressed in all NA +P62258 14-3-3 protein epsilon 4 ENSG00000108953; ENSG00000274474 YWHAE Tyrosine 3-monooxygenase/tryptophan 5-monooxygenase activation protein, epsilon Expressed in all NA +P68871 Hemoglobin subunit beta 4 ENSG00000244734 HBB Hemoglobin, beta Tissue enriched bone marrow: 78261.0 +Q9C075 Keratin, type I cytoskeletal 23 4 ENSG00000108244; ENSG00000263309 KRT23 Keratin 23, type I Tissue enhanced placenta: 68.3;skin: 71.0 +A8K2U0 Alpha-2-macroglobulin-like protein 1 3 ENSG00000166535 A2ML1 Alpha-2-macroglobulin-like 1 Tissue enriched esophagus: 480.8 +P00738 Haptoglobin 3 ENSG00000257017 HP Haptoglobin Tissue enriched liver: 28321.0 +P01011 Alpha-1-antichymotrypsin 3 ENSG00000196136 SERPINA3 Serpin peptidase inhibitor, clade A (alpha-1 antiproteinase, antitrypsin), member 3 Group enriched cervix, uterine: 133.1;liver: 607.5 +P02763 Alpha-1-acid glycoprotein 1 3 ENSG00000229314 ORM1 Orosomucoid 1 Tissue enriched liver: 10546.0 +P18510 Interleukin-1 receptor antagonist protein 3 ENSG00000136689 IL1RN Interleukin 1 receptor antagonist Tissue enhanced esophagus: 1248.5 +P22528 Cornifin-B 3 ENSG00000169469 SPRR1B Small proline-rich protein 1B Tissue enriched esophagus: 2466.0 +P30740 Leukocyte elastase inhibitor 3 ENSG00000021355 SERPINB1 Serpin peptidase inhibitor, clade B (ovalbumin), member 1 Expressed in all NA +P80188 Neutrophil gelatinase-associated lipocalin 3 ENSG00000148346 LCN2 Lipocalin 2 Tissue enhanced bone marrow: 1855.7;gallbladder: 3437.6 +Q15828 Cystatin-M 3 ENSG00000175315 CST6 Cystatin E/M Tissue enriched skin: 213.3 +Q9HCY8 Protein S100-A14 3 ENSG00000189334 S100A14 S100 calcium binding protein A14 Tissue enhanced esophagus: 2214.5 +P01623 Ig kappa chain V-III region 3 NA NA NA NA NA +P01877 Ig alpha-2 chain C region 3 ENSG00000211890 NA NA NA NA +P06396 Gelsolin 3 ENSG00000148180 GSN Gelsolin Expressed in all NA +P14735 Insulin-degrading enzyme 3 ENSG00000119912 IDE Insulin-degrading enzyme Expressed in all NA +P20933 N(4)-(beta-N-acetylglucosaminyl)-L-asparaginase 3 ENSG00000038002 AGA Aspartylglucosaminidase Expressed in all NA +P25788 Proteasome subunit alpha type-3 3 ENSG00000100567 PSMA3 Proteasome subunit alpha 3 Expressed in all NA +P26641 Elongation factor 1-gamma 3 ENSG00000254772 EEF1G Eukaryotic translation elongation factor 1 gamma Expressed in all NA +P36952 Serpin B5 3 ENSG00000206075 SERPINB5 Serpin peptidase inhibitor, clade B (ovalbumin), member 5 Group enriched esophagus: 221.1;skin: 262.5 +P40926 Malate dehydrogenase, mitochondrial 3 ENSG00000146701 MDH2 Malate dehydrogenase 2, NAD (mitochondrial) Expressed in all NA +Q9Y6R7 IgGFc-binding protein 3 ENSG00000281123 NA NA NA NA +O95274 Ly6/PLAUR domain-containing protein 3 2 ENSG00000124466 LYPD3 LY6/PLAUR domain containing 3 Group enriched esophagus: 676.5;skin: 594.5 +P00491 Purine nucleoside phosphorylase 2 ENSG00000198805 PNP Purine nucleoside phosphorylase Expressed in all NA +P04080 Cystatin-B 2 ENSG00000160213 CSTB Cystatin B (stefin B) Tissue enriched esophagus: 1836.3 +P09972 Fructose-bisphosphate aldolase C 2 ENSG00000109107 ALDOC Aldolase C, fructose-bisphosphate Tissue enriched cerebral cortex: 768.7 +P19012 Keratin, type I cytoskeletal 15 2 ENSG00000171346 KRT15 Keratin 15, type I Group enriched breast: 320.0;esophagus: 787.5;skin: 1012.3 +P20930 Filaggrin 2 ENSG00000143631 FLG Filaggrin Tissue enriched skin: 549.7 +Q96FX8 p53 apoptosis effector related to PMP-22 2 ENSG00000112378 PERP PERP, TP53 apoptosis effector Group enriched esophagus: 574.1;skin: 1238.6 +Q9UIV8 Serpin B13 2 ENSG00000197641 SERPINB13 Serpin peptidase inhibitor, clade B (ovalbumin), member 13 Tissue enriched esophagus: 185.3 +P01625 Ig kappa chain V-IV region Len 2 NA NA NA NA NA +P01765 Ig heavy chain V-III region TIL 2 NA NA NA NA NA +P01766 Ig heavy chain V-III region BRO 2 ENSG00000211942; ENSG00000282286 NA NA NA NA +P01860 Ig gamma-3 chain C region 2 NA NA NA NA NA +P01871 Ig mu chain C region 2 ENSG00000211899; ENSG00000282657 NA NA NA NA +P05090 Apolipoprotein D 2 ENSG00000189058 APOD Apolipoprotein D Tissue enriched breast: 4546.8 +P07858 Cathepsin B 2 ENSG00000164733 CTSB Cathepsin B Expressed in all NA +P08865 40S ribosomal protein SA 2 ENSG00000168028 RPSA Ribosomal protein SA Expressed in all NA +P11279 Lysosome-associated membrane glycoprotein 1 2 ENSG00000185896 LAMP1 Lysosomal-associated membrane protein 1 Expressed in all NA +P13473 Lysosome-associated membrane glycoprotein 2 2 ENSG00000005893 LAMP2 Lysosomal-associated membrane protein 2 Expressed in all NA +P19971 Thymidine phosphorylase 2 ENSG00000025708 TYMP Thymidine phosphorylase Tissue enhanced appendix: 103.2 +P23284 Peptidyl-prolyl cis-trans isomerase B 2 ENSG00000166794 PPIB Peptidylprolyl isomerase B (cyclophilin B) Expressed in all NA +P23396 40S ribosomal protein S3 2 ENSG00000149273 RPS3 Ribosomal protein S3 Expressed in all NA +P25705 ATP synthase subunit alpha, mitochondrial 2 ENSG00000152234 ATP5A1 ATP synthase, H+ transporting, mitochondrial F1 complex, alpha subunit 1, cardiac muscle Expressed in all NA +P27482 Calmodulin-like protein 3 2 ENSG00000178363 CALML3 Calmodulin-like 3 Tissue enhanced esophagus: 166.4;skin: 42.7 +P31949 Protein S100-A11 2 ENSG00000163191 S100A11 S100 calcium binding protein A11 Expressed in all NA +P40121 Macrophage-capping protein 2 ENSG00000042493 CAPG Capping protein (actin filament), gelsolin-like Expressed in all NA +P42357 Histidine ammonia-lyase 2 ENSG00000084110 HAL Histidine ammonia-lyase Group enriched liver: 51.0;skin: 72.6 +P47756 F-actin-capping protein subunit beta 2 ENSG00000077549 CAPZB Capping protein (actin filament) muscle Z-line, beta Expressed in all NA +P48637 Glutathione synthetase 2 ENSG00000100983 GSS Glutathione synthetase Expressed in all NA +P49720 Proteasome subunit beta type-3 2 ENSG00000277791; ENSG00000275903 PSMB3 Proteasome subunit beta 3 Expressed in all NA +P50395 Rab GDP dissociation inhibitor beta 2 ENSG00000057608 GDI2 GDP dissociation inhibitor 2 Expressed in all NA +P59998 Actin-related protein 2/3 complex subunit 4 2 ENSG00000241553 ARPC4 Actin related protein 2/3 complex, subunit 4, 20kDa Expressed in all NA +P61160 Actin-related protein 2 2 ENSG00000138071 ACTR2 ARP2 actin-related protein 2 homolog (yeast) Expressed in all NA +P61916 Epididymal secretory protein E1 2 ENSG00000119655 NPC2 Niemann-Pick disease, type C2 Tissue enriched epididymis: 16057.0
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/mouse_geneID.txt Tue Dec 18 09:21:32 2018 -0500 @@ -0,0 +1,231 @@ +27053 +20860 +217845 +17748 +74568 +17750 +56150 +102502 +225884 +227620 +67103 +12856 +110078 +16069 +22240 +107569 +20753 +22218 +105298 +11636 +17975 +12332 +192176 +76650 +234663 +16765 +74551 +12580 +68441 +15381 +15507 +16181 +114774 +22323 +21810 +76281 +67144 +238055 +217069 +98415 +53415 +72275 +68219 +242687 +104759 +14864 +54138 +66144 +19656 +19659 +11853 +50915 +14114 +12798 +12028 +230753 +17524 +22350 +66395 +27357 +226654 +65964 +19039 +13821 +107589 +17931 +69694 +19240 +11677 +NA +67290 +239217 +67938 +15463 +100042295 +67092 +18104 +110052 +211666 +69787 +66060 +105348 +225884 +17068 +74122 +216350 +NA +17075 +72303 +231655 +445007 +12796 +13086 +12490 +27053 +22350 +15388 +217845 +66120 +11647 +242291 +68556 +56215 +13211 +72657 +223921 +77106 +21985 +13118 +384009 +20218 +17149 +14548 +72787 +54138 +225027 +14105 +81898 +68981 +331401 +100038882 +56857 +83701 +19383 +223672 +20637 +20823 +110809 +NA +20860 +19223 +72082 +29875 +19192 +68693 +68087 +67938 +230257 +57278 +386612 +19659 +72027 +236539 +21681 +239017 +434080 +20630 +17476 +142980 +13046 +20624 +66184 +67068 +53607 +21838 +20384 +11677 +15463 +18054 +107686 +331487 +230908 +50926 +15384 +72040 +15381 +20462 +67465 +11766 +17304 +71960 +246730 +30934 +12293 +11852 +20336 +80860 +100317 +17184 +74326 +13179 +20773 +66395 +245688 +77134 +112417 +75062 +66058 +53379 +71733 +229279 +19656 +74558 +17063 +28000 +226101 +14999 +105298 +17454 +29816 +16414 +219158 +17079 +68953 +56705 +67040 +74125 +20719 +67657 +21767 +109815 +192159 +15211 +13204 +105501 +71660 +67144 +68565 +29864 +53357 +67103 +227620 +269774 +66585 +67996 +11991 +224045 +69150 +99889 +71514 +16852
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/universe.csv Tue Dec 18 09:21:32 2018 -0500 @@ -0,0 +1,14624 @@ +Gene Gene.name Tissue Cell.type Level Reliability UniProt.AC +ENSG00000001167 NFYA epididymis glandular cells Medium Enhanced P23511 +ENSG00000001167 NFYA prostate glandular cells Medium Enhanced P23511 +ENSG00000001167 NFYA seminal vesicle glandular cells Medium Enhanced P23511 +ENSG00000001167 NFYA testis cells in seminiferous ducts Medium Enhanced P23511 +ENSG00000001167 NFYA testis Leydig cells Medium Enhanced P23511 +ENSG00000001497 LAS1L epididymis glandular cells High Supported Q9Y4W2 +ENSG00000001497 LAS1L prostate glandular cells Medium Supported Q9Y4W2 +ENSG00000001497 LAS1L seminal vesicle glandular cells High Supported Q9Y4W2 +ENSG00000001497 LAS1L testis cells in seminiferous ducts High Supported Q9Y4W2 +ENSG00000001497 LAS1L testis Leydig cells High Supported Q9Y4W2 +ENSG00000001630 CYP51A1 testis Leydig cells High Enhanced Q16850 +ENSG00000002549 LAP3 epididymis glandular cells Medium Enhanced P28838 +ENSG00000002549 LAP3 prostate glandular cells Medium Enhanced P28838 +ENSG00000002549 LAP3 seminal vesicle glandular cells Medium Enhanced P28838 +ENSG00000002549 LAP3 testis cells in seminiferous ducts Medium Enhanced P28838 +ENSG00000002549 LAP3 testis Leydig cells Low Enhanced P28838 +ENSG00000002586 CD99 epididymis glandular cells Low Supported P14209 +ENSG00000002586 CD99 prostate glandular cells High Supported P14209 +ENSG00000002586 CD99 seminal vesicle glandular cells Medium Supported P14209 +ENSG00000002586 CD99 testis cells in seminiferous ducts High Supported P14209 +ENSG00000002822 MAD1L1 epididymis glandular cells High Supported Q9Y6D9 +ENSG00000002822 MAD1L1 prostate glandular cells Medium Supported Q9Y6D9 +ENSG00000002822 MAD1L1 seminal vesicle glandular cells Medium Supported Q9Y6D9 +ENSG00000002822 MAD1L1 testis cells in seminiferous ducts High Supported Q9Y6D9 +ENSG00000002822 MAD1L1 testis Leydig cells Medium Supported Q9Y6D9 +ENSG00000003436 TFPI epididymis glandular cells Medium Supported P10646 +ENSG00000003436 TFPI prostate glandular cells Medium Supported P10646 +ENSG00000003436 TFPI seminal vesicle glandular cells Medium Supported P10646 +ENSG00000003436 TFPI testis cells in seminiferous ducts Low Supported P10646 +ENSG00000003436 TFPI testis Leydig cells Medium Supported P10646 +ENSG00000004468 CD38 prostate glandular cells High Enhanced P28907 +ENSG00000004468 CD38 seminal vesicle glandular cells High Enhanced P28907 +ENSG00000004478 FKBP4 epididymis glandular cells Medium Enhanced Q02790 +ENSG00000004478 FKBP4 prostate glandular cells Medium Enhanced Q02790 +ENSG00000004478 FKBP4 testis cells in seminiferous ducts Medium Enhanced Q02790 +ENSG00000004478 FKBP4 testis Leydig cells Low Enhanced Q02790 +ENSG00000004487 KDM1A epididymis glandular cells Medium Supported O60341 +ENSG00000004487 KDM1A seminal vesicle glandular cells Medium Supported O60341 +ENSG00000004487 KDM1A testis cells in seminiferous ducts Medium Supported O60341 +ENSG00000004534 RBM6 epididymis glandular cells High Enhanced P78332 +ENSG00000004534 RBM6 prostate glandular cells High Enhanced P78332 +ENSG00000004534 RBM6 seminal vesicle glandular cells Low Enhanced P78332 +ENSG00000004534 RBM6 testis cells in seminiferous ducts High Enhanced P78332 +ENSG00000004534 RBM6 testis Leydig cells High Enhanced P78332 +ENSG00000004700 RECQL epididymis glandular cells Medium Enhanced P46063 +ENSG00000004700 RECQL seminal vesicle glandular cells Low Enhanced P46063 +ENSG00000004700 RECQL testis cells in seminiferous ducts Medium Enhanced P46063 +ENSG00000004700 RECQL testis Leydig cells Medium Enhanced P46063 +ENSG00000004776 HSPB6 testis Leydig cells High Enhanced O14558 +ENSG00000004777 ARHGAP33 epididymis glandular cells Medium Supported O14559 +ENSG00000004777 ARHGAP33 prostate glandular cells Medium Supported O14559 +ENSG00000004777 ARHGAP33 seminal vesicle glandular cells Low Supported O14559 +ENSG00000004777 ARHGAP33 testis cells in seminiferous ducts Medium Supported O14559 +ENSG00000004777 ARHGAP33 testis Leydig cells Low Supported O14559 +ENSG00000004897 CDC27 epididymis glandular cells Medium Supported P30260 +ENSG00000004897 CDC27 prostate glandular cells Low Supported P30260 +ENSG00000004897 CDC27 seminal vesicle glandular cells Medium Supported P30260 +ENSG00000004897 CDC27 testis cells in seminiferous ducts Medium Supported P30260 +ENSG00000004897 CDC27 testis Leydig cells Low Supported P30260 +ENSG00000004948 CALCR testis Leydig cells Low Enhanced P30988 +ENSG00000005059 MCUB prostate glandular cells Low Enhanced Q9NWR8 +ENSG00000005073 HOXA11 prostate glandular cells Low Enhanced P31270 +ENSG00000005108 THSD7A testis Leydig cells Medium Supported Q9UPZ6 +ENSG00000005156 LIG3 epididymis glandular cells High Supported P49916 +ENSG00000005156 LIG3 prostate glandular cells Medium Supported P49916 +ENSG00000005156 LIG3 seminal vesicle glandular cells Medium Supported P49916 +ENSG00000005156 LIG3 testis cells in seminiferous ducts High Supported P49916 +ENSG00000005156 LIG3 testis Leydig cells Low Supported P49916 +ENSG00000005175 RPAP3 epididymis glandular cells Medium Enhanced Q9H6T3 +ENSG00000005175 RPAP3 prostate glandular cells Medium Enhanced Q9H6T3 +ENSG00000005175 RPAP3 seminal vesicle glandular cells Medium Enhanced Q9H6T3 +ENSG00000005175 RPAP3 testis cells in seminiferous ducts Medium Enhanced Q9H6T3 +ENSG00000005175 RPAP3 testis Leydig cells Medium Enhanced Q9H6T3 +ENSG00000005189 AC004381.6 prostate glandular cells Medium Enhanced Q96IC2 +ENSG00000005189 AC004381.6 seminal vesicle glandular cells Medium Enhanced Q96IC2 +ENSG00000005189 AC004381.6 testis cells in seminiferous ducts Medium Enhanced Q96IC2 +ENSG00000005189 AC004381.6 testis Leydig cells Medium Enhanced Q96IC2 +ENSG00000005194 CIAPIN1 epididymis glandular cells Low Enhanced Q6FI81 +ENSG00000005194 CIAPIN1 prostate glandular cells Low Enhanced Q6FI81 +ENSG00000005194 CIAPIN1 testis cells in seminiferous ducts High Enhanced Q6FI81 +ENSG00000005194 CIAPIN1 testis Leydig cells Low Enhanced Q6FI81 +ENSG00000005249 PRKAR2B epididymis glandular cells Medium Enhanced NA +ENSG00000005249 PRKAR2B prostate glandular cells Low Enhanced NA +ENSG00000005249 PRKAR2B testis cells in seminiferous ducts Medium Enhanced NA +ENSG00000005249 PRKAR2B testis Leydig cells Medium Enhanced NA +ENSG00000005339 CREBBP epididymis glandular cells Medium Enhanced Q92793 +ENSG00000005339 CREBBP prostate glandular cells Medium Enhanced Q92793 +ENSG00000005339 CREBBP seminal vesicle glandular cells Medium Enhanced Q92793 +ENSG00000005339 CREBBP testis cells in seminiferous ducts High Enhanced Q92793 +ENSG00000005339 CREBBP testis Leydig cells High Enhanced Q92793 +ENSG00000005379 TSPOAP1 epididymis glandular cells Medium Enhanced O95153 +ENSG00000005379 TSPOAP1 prostate glandular cells Medium Enhanced O95153 +ENSG00000005379 TSPOAP1 seminal vesicle glandular cells Low Enhanced O95153 +ENSG00000005379 TSPOAP1 testis cells in seminiferous ducts Medium Enhanced O95153 +ENSG00000005379 TSPOAP1 testis Leydig cells Medium Enhanced O95153 +ENSG00000005448 WDR54 epididymis glandular cells Medium Enhanced Q9H977 +ENSG00000005448 WDR54 prostate glandular cells Low Enhanced Q9H977 +ENSG00000005448 WDR54 seminal vesicle glandular cells Medium Enhanced Q9H977 +ENSG00000005448 WDR54 testis cells in seminiferous ducts Medium Enhanced Q9H977 +ENSG00000005469 CROT epididymis glandular cells Low Enhanced Q9UKG9 +ENSG00000005469 CROT prostate glandular cells Low Enhanced Q9UKG9 +ENSG00000005469 CROT seminal vesicle glandular cells Medium Enhanced Q9UKG9 +ENSG00000005469 CROT testis cells in seminiferous ducts Low Enhanced Q9UKG9 +ENSG00000005469 CROT testis Leydig cells Medium Enhanced Q9UKG9 +ENSG00000005513 SOX8 testis cells in seminiferous ducts Low Enhanced P57073 +ENSG00000005882 PDK2 epididymis glandular cells Medium Supported Q15119 +ENSG00000005882 PDK2 prostate glandular cells Medium Supported Q15119 +ENSG00000005882 PDK2 seminal vesicle glandular cells Medium Supported Q15119 +ENSG00000005882 PDK2 testis cells in seminiferous ducts High Supported Q15119 +ENSG00000005882 PDK2 testis Leydig cells Medium Supported Q15119 +ENSG00000005884 ITGA3 epididymis glandular cells Medium Enhanced P26006 +ENSG00000005884 ITGA3 prostate glandular cells Medium Enhanced P26006 +ENSG00000005884 ITGA3 seminal vesicle glandular cells Medium Enhanced P26006 +ENSG00000005884 ITGA3 testis cells in seminiferous ducts Low Enhanced P26006 +ENSG00000005884 ITGA3 testis Leydig cells Medium Enhanced P26006 +ENSG00000005889 ZFX epididymis glandular cells Medium Supported P17010 +ENSG00000005889 ZFX prostate glandular cells Medium Supported P17010 +ENSG00000005889 ZFX seminal vesicle glandular cells Medium Supported P17010 +ENSG00000005889 ZFX testis cells in seminiferous ducts Medium Supported P17010 +ENSG00000005889 ZFX testis Leydig cells Medium Supported P17010 +ENSG00000005893 LAMP2 epididymis glandular cells High Enhanced P13473 +ENSG00000005893 LAMP2 prostate glandular cells High Enhanced P13473 +ENSG00000005893 LAMP2 seminal vesicle glandular cells Medium Enhanced P13473 +ENSG00000005893 LAMP2 testis cells in seminiferous ducts Medium Enhanced P13473 +ENSG00000005893 LAMP2 testis Leydig cells High Enhanced P13473 +ENSG00000006047 YBX2 testis elongated or late spermatids High Enhanced Q9Y2T7 +ENSG00000006047 YBX2 testis Leydig cells Low Enhanced Q9Y2T7 +ENSG00000006047 YBX2 testis pachytene spermatocytes High Enhanced Q9Y2T7 +ENSG00000006047 YBX2 testis preleptotene spermatocytes Low Enhanced Q9Y2T7 +ENSG00000006047 YBX2 testis round or early spermatids High Enhanced Q9Y2T7 +ENSG00000006047 YBX2 testis spermatogonia Low Enhanced Q9Y2T7 +ENSG00000006118 TMEM132A seminal vesicle glandular cells Low Enhanced Q24JP5 +ENSG00000006118 TMEM132A testis Leydig cells Low Enhanced Q24JP5 +ENSG00000006282 SPATA20 epididymis glandular cells Medium Enhanced Q8TB22 +ENSG00000006282 SPATA20 seminal vesicle glandular cells Low Enhanced Q8TB22 +ENSG00000006282 SPATA20 testis cells in seminiferous ducts High Enhanced Q8TB22 +ENSG00000006282 SPATA20 testis Leydig cells Medium Enhanced Q8TB22 +ENSG00000006453 BAIAP2L1 epididymis glandular cells Low Enhanced Q9UHR4 +ENSG00000006453 BAIAP2L1 prostate glandular cells High Enhanced Q9UHR4 +ENSG00000006453 BAIAP2L1 seminal vesicle glandular cells Low Enhanced Q9UHR4 +ENSG00000006453 BAIAP2L1 testis cells in seminiferous ducts Low Enhanced Q9UHR4 +ENSG00000006453 BAIAP2L1 testis Leydig cells Low Enhanced Q9UHR4 +ENSG00000006530 AGK epididymis glandular cells Medium Supported E9PG39 +ENSG00000006530 AGK prostate glandular cells Medium Supported E9PG39 +ENSG00000006530 AGK seminal vesicle glandular cells High Supported E9PG39 +ENSG00000006530 AGK testis cells in seminiferous ducts Medium Supported E9PG39 +ENSG00000006530 AGK testis Leydig cells High Supported E9PG39 +ENSG00000006611 USH1C epididymis glandular cells Low Supported Q9Y6N9 +ENSG00000006611 USH1C testis cells in seminiferous ducts Low Supported Q9Y6N9 +ENSG00000006695 COX10 epididymis glandular cells High Supported Q12887 +ENSG00000006695 COX10 prostate glandular cells Medium Supported Q12887 +ENSG00000006695 COX10 seminal vesicle glandular cells Medium Supported Q12887 +ENSG00000006695 COX10 testis cells in seminiferous ducts Medium Supported Q12887 +ENSG00000006695 COX10 testis Leydig cells Medium Supported Q12887 +ENSG00000006747 SCIN seminal vesicle glandular cells Low Enhanced Q9Y6U3 +ENSG00000007038 PRSS21 testis elongated or late spermatids Medium Enhanced NA +ENSG00000007038 PRSS21 testis Leydig cells Low Enhanced NA +ENSG00000007038 PRSS21 testis pachytene spermatocytes High Enhanced NA +ENSG00000007038 PRSS21 testis preleptotene spermatocytes Low Enhanced NA +ENSG00000007038 PRSS21 testis round or early spermatids High Enhanced NA +ENSG00000007062 PROM1 epididymis glandular cells Medium Enhanced O43490 +ENSG00000007062 PROM1 seminal vesicle glandular cells Medium Enhanced O43490 +ENSG00000007080 CCDC124 epididymis glandular cells High Supported Q96CT7 +ENSG00000007080 CCDC124 prostate glandular cells Medium Supported Q96CT7 +ENSG00000007080 CCDC124 seminal vesicle glandular cells High Supported Q96CT7 +ENSG00000007080 CCDC124 testis cells in seminiferous ducts High Supported Q96CT7 +ENSG00000007080 CCDC124 testis Leydig cells Medium Supported Q96CT7 +ENSG00000007216 SLC13A2 seminal vesicle glandular cells Medium Enhanced Q13183 +ENSG00000007350 TKTL1 testis elongated or late spermatids High Enhanced P51854 +ENSG00000007350 TKTL1 testis pachytene spermatocytes Medium Enhanced P51854 +ENSG00000007350 TKTL1 testis preleptotene spermatocytes High Enhanced P51854 +ENSG00000007350 TKTL1 testis round or early spermatids Medium Enhanced P51854 +ENSG00000007350 TKTL1 testis spermatogonia High Enhanced P51854 +ENSG00000007392 LUC7L epididymis glandular cells High Supported Q9NQ29 +ENSG00000007392 LUC7L prostate glandular cells Medium Supported Q9NQ29 +ENSG00000007392 LUC7L seminal vesicle glandular cells Medium Supported Q9NQ29 +ENSG00000007392 LUC7L testis cells in seminiferous ducts High Supported Q9NQ29 +ENSG00000007392 LUC7L testis Leydig cells Medium Supported Q9NQ29 +ENSG00000007933 FMO3 epididymis glandular cells Low Enhanced P31513 +ENSG00000007933 FMO3 testis Leydig cells Low Enhanced P31513 +ENSG00000008018 PSMB1 epididymis glandular cells Medium Enhanced P20618 +ENSG00000008018 PSMB1 prostate glandular cells Medium Enhanced P20618 +ENSG00000008018 PSMB1 seminal vesicle glandular cells Medium Enhanced P20618 +ENSG00000008018 PSMB1 testis cells in seminiferous ducts High Enhanced P20618 +ENSG00000008018 PSMB1 testis Leydig cells High Enhanced P20618 +ENSG00000008086 CDKL5 epididymis glandular cells Low Supported O76039 +ENSG00000008086 CDKL5 prostate glandular cells Low Supported O76039 +ENSG00000008086 CDKL5 seminal vesicle glandular cells Low Supported O76039 +ENSG00000008086 CDKL5 testis cells in seminiferous ducts Low Supported O76039 +ENSG00000008086 CDKL5 testis Leydig cells Medium Supported O76039 +ENSG00000008128 CDK11A epididymis glandular cells Medium Enhanced Q9UQ88 +ENSG00000008128 CDK11A prostate glandular cells Medium Enhanced Q9UQ88 +ENSG00000008128 CDK11A seminal vesicle glandular cells High Enhanced Q9UQ88 +ENSG00000008128 CDK11A testis cells in seminiferous ducts Medium Enhanced Q9UQ88 +ENSG00000008128 CDK11A testis Leydig cells Low Enhanced Q9UQ88 +ENSG00000008196 TFAP2B epididymis glandular cells High Supported Q92481 +ENSG00000008196 TFAP2B seminal vesicle glandular cells Medium Supported Q92481 +ENSG00000008226 DLEC1 testis elongated or late spermatids Low Enhanced Q9Y238 +ENSG00000008226 DLEC1 testis Leydig cells Low Enhanced Q9Y238 +ENSG00000008226 DLEC1 testis pachytene spermatocytes Low Enhanced Q9Y238 +ENSG00000008226 DLEC1 testis preleptotene spermatocytes Medium Enhanced Q9Y238 +ENSG00000008226 DLEC1 testis round or early spermatids Low Enhanced Q9Y238 +ENSG00000008311 AASS epididymis glandular cells Low Enhanced Q9UDR5 +ENSG00000008311 AASS prostate glandular cells Medium Enhanced Q9UDR5 +ENSG00000008311 AASS seminal vesicle glandular cells Medium Enhanced Q9UDR5 +ENSG00000008311 AASS testis cells in seminiferous ducts Low Enhanced Q9UDR5 +ENSG00000008311 AASS testis Leydig cells Medium Enhanced Q9UDR5 +ENSG00000008394 MGST1 prostate glandular cells Medium Enhanced P10620 +ENSG00000008394 MGST1 seminal vesicle glandular cells Low Enhanced P10620 +ENSG00000008394 MGST1 testis cells in seminiferous ducts Medium Enhanced P10620 +ENSG00000008394 MGST1 testis Leydig cells Medium Enhanced P10620 +ENSG00000008441 NFIX epididymis glandular cells Medium Supported Q14938 +ENSG00000008441 NFIX prostate glandular cells High Supported Q14938 +ENSG00000008441 NFIX seminal vesicle glandular cells Medium Supported Q14938 +ENSG00000008441 NFIX testis Leydig cells High Supported Q14938 +ENSG00000009307 CSDE1 epididymis glandular cells Medium Enhanced O75534 +ENSG00000009307 CSDE1 prostate glandular cells Medium Enhanced O75534 +ENSG00000009307 CSDE1 seminal vesicle glandular cells Medium Enhanced O75534 +ENSG00000009307 CSDE1 testis cells in seminiferous ducts Medium Enhanced O75534 +ENSG00000009307 CSDE1 testis Leydig cells Medium Enhanced O75534 +ENSG00000009790 TRAF3IP3 epididymis glandular cells Low Enhanced Q9Y228 +ENSG00000009790 TRAF3IP3 prostate glandular cells Low Enhanced Q9Y228 +ENSG00000009790 TRAF3IP3 testis Leydig cells Low Enhanced Q9Y228 +ENSG00000009954 BAZ1B epididymis glandular cells Medium Supported Q9UIG0 +ENSG00000009954 BAZ1B prostate glandular cells Medium Supported Q9UIG0 +ENSG00000009954 BAZ1B seminal vesicle glandular cells Medium Supported Q9UIG0 +ENSG00000009954 BAZ1B testis cells in seminiferous ducts Medium Supported Q9UIG0 +ENSG00000009954 BAZ1B testis Leydig cells Medium Supported Q9UIG0 +ENSG00000010244 ZNF207 epididymis glandular cells High Enhanced O43670 +ENSG00000010244 ZNF207 prostate glandular cells High Enhanced O43670 +ENSG00000010244 ZNF207 seminal vesicle glandular cells High Enhanced O43670 +ENSG00000010244 ZNF207 testis cells in seminiferous ducts High Enhanced O43670 +ENSG00000010244 ZNF207 testis Leydig cells High Enhanced O43670 +ENSG00000010256 UQCRC1 epididymis glandular cells High Enhanced P31930 +ENSG00000010256 UQCRC1 prostate glandular cells High Enhanced P31930 +ENSG00000010256 UQCRC1 seminal vesicle glandular cells High Enhanced P31930 +ENSG00000010256 UQCRC1 testis cells in seminiferous ducts High Enhanced P31930 +ENSG00000010256 UQCRC1 testis Leydig cells High Enhanced P31930 +ENSG00000010270 STARD3NL epididymis glandular cells High Enhanced O95772 +ENSG00000010270 STARD3NL prostate glandular cells Medium Enhanced O95772 +ENSG00000010270 STARD3NL seminal vesicle glandular cells Medium Enhanced O95772 +ENSG00000010270 STARD3NL testis cells in seminiferous ducts Medium Enhanced O95772 +ENSG00000010270 STARD3NL testis Leydig cells Medium Enhanced O95772 +ENSG00000010278 CD9 epididymis glandular cells Medium Supported P21926 +ENSG00000010278 CD9 prostate glandular cells High Supported P21926 +ENSG00000010278 CD9 seminal vesicle glandular cells High Supported P21926 +ENSG00000010278 CD9 testis cells in seminiferous ducts Medium Supported P21926 +ENSG00000010278 CD9 testis Leydig cells Medium Supported P21926 +ENSG00000010292 NCAPD2 epididymis glandular cells Medium Supported Q15021 +ENSG00000010292 NCAPD2 prostate glandular cells Medium Supported Q15021 +ENSG00000010292 NCAPD2 seminal vesicle glandular cells Medium Supported Q15021 +ENSG00000010292 NCAPD2 testis cells in seminiferous ducts Medium Supported Q15021 +ENSG00000010292 NCAPD2 testis Leydig cells Medium Supported Q15021 +ENSG00000010318 PHF7 testis elongated or late spermatids High Enhanced Q9BWX1 +ENSG00000010318 PHF7 testis Leydig cells Low Enhanced Q9BWX1 +ENSG00000010318 PHF7 testis pachytene spermatocytes Medium Enhanced Q9BWX1 +ENSG00000010318 PHF7 testis round or early spermatids Medium Enhanced Q9BWX1 +ENSG00000010626 LRRC23 testis elongated or late spermatids High Enhanced Q53EV4 +ENSG00000010626 LRRC23 testis pachytene spermatocytes High Enhanced Q53EV4 +ENSG00000010626 LRRC23 testis preleptotene spermatocytes Low Enhanced Q53EV4 +ENSG00000010626 LRRC23 testis round or early spermatids High Enhanced Q53EV4 +ENSG00000010626 LRRC23 testis spermatogonia Low Enhanced Q53EV4 +ENSG00000011028 MRC2 epididymis glandular cells Low Enhanced Q9UBG0 +ENSG00000011028 MRC2 prostate glandular cells Low Enhanced Q9UBG0 +ENSG00000011028 MRC2 seminal vesicle glandular cells Low Enhanced Q9UBG0 +ENSG00000011028 MRC2 testis cells in seminiferous ducts Low Enhanced Q9UBG0 +ENSG00000011028 MRC2 testis Leydig cells High Enhanced Q9UBG0 +ENSG00000011143 MKS1 epididymis glandular cells High Enhanced Q9NXB0 +ENSG00000011143 MKS1 prostate glandular cells High Enhanced Q9NXB0 +ENSG00000011143 MKS1 seminal vesicle glandular cells Medium Enhanced Q9NXB0 +ENSG00000011243 AKAP8L epididymis glandular cells High Enhanced Q9ULX6 +ENSG00000011243 AKAP8L prostate glandular cells Medium Enhanced Q9ULX6 +ENSG00000011243 AKAP8L seminal vesicle glandular cells High Enhanced Q9ULX6 +ENSG00000011243 AKAP8L testis cells in seminiferous ducts High Enhanced Q9ULX6 +ENSG00000011243 AKAP8L testis Leydig cells Medium Enhanced Q9ULX6 +ENSG00000011275 RNF216 epididymis glandular cells Low Supported Q9NWF9 +ENSG00000011275 RNF216 prostate glandular cells Low Supported Q9NWF9 +ENSG00000011275 RNF216 seminal vesicle glandular cells Low Supported Q9NWF9 +ENSG00000011275 RNF216 testis cells in seminiferous ducts Medium Supported Q9NWF9 +ENSG00000011275 RNF216 testis Leydig cells Medium Supported Q9NWF9 +ENSG00000011295 TTC19 epididymis glandular cells Medium Enhanced Q6DKK2 +ENSG00000011295 TTC19 prostate glandular cells Medium Enhanced Q6DKK2 +ENSG00000011295 TTC19 seminal vesicle glandular cells Medium Enhanced Q6DKK2 +ENSG00000011295 TTC19 testis cells in seminiferous ducts Medium Enhanced Q6DKK2 +ENSG00000011295 TTC19 testis Leydig cells Medium Enhanced Q6DKK2 +ENSG00000011304 PTBP1 epididymis glandular cells High Supported P26599 +ENSG00000011304 PTBP1 prostate glandular cells Medium Supported P26599 +ENSG00000011304 PTBP1 seminal vesicle glandular cells High Supported P26599 +ENSG00000011304 PTBP1 testis cells in seminiferous ducts High Supported P26599 +ENSG00000011304 PTBP1 testis Leydig cells High Supported P26599 +ENSG00000011332 DPF1 testis cells in seminiferous ducts Low Enhanced Q92782 +ENSG00000011347 SYT7 prostate glandular cells High Enhanced O43581 +ENSG00000011426 ANLN testis cells in seminiferous ducts High Enhanced Q9NQW6 +ENSG00000011451 WIZ epididymis glandular cells High Supported O95785 +ENSG00000011451 WIZ prostate glandular cells High Supported O95785 +ENSG00000011451 WIZ seminal vesicle glandular cells High Supported O95785 +ENSG00000011451 WIZ testis cells in seminiferous ducts High Supported O95785 +ENSG00000011451 WIZ testis Leydig cells High Supported O95785 +ENSG00000011454 RABGAP1 epididymis glandular cells High Enhanced Q9Y3P9 +ENSG00000011454 RABGAP1 prostate glandular cells Medium Enhanced Q9Y3P9 +ENSG00000011454 RABGAP1 seminal vesicle glandular cells Medium Enhanced Q9Y3P9 +ENSG00000011454 RABGAP1 testis cells in seminiferous ducts High Enhanced Q9Y3P9 +ENSG00000011454 RABGAP1 testis Leydig cells Medium Enhanced Q9Y3P9 +ENSG00000011523 CEP68 epididymis glandular cells Medium Enhanced Q76N32 +ENSG00000011523 CEP68 prostate glandular cells Medium Enhanced Q76N32 +ENSG00000011523 CEP68 seminal vesicle glandular cells Medium Enhanced Q76N32 +ENSG00000011523 CEP68 testis cells in seminiferous ducts Medium Enhanced Q76N32 +ENSG00000011523 CEP68 testis Leydig cells Medium Enhanced Q76N32 +ENSG00000011590 ZBTB32 epididymis glandular cells Low Enhanced Q9Y2Y4 +ENSG00000011590 ZBTB32 testis cells in seminiferous ducts Medium Enhanced Q9Y2Y4 +ENSG00000011600 TYROBP epididymis glandular cells Low Enhanced O43914 +ENSG00000011600 TYROBP prostate glandular cells Low Enhanced O43914 +ENSG00000011600 TYROBP seminal vesicle glandular cells Low Enhanced O43914 +ENSG00000012048 BRCA1 epididymis glandular cells Medium Enhanced P38398 +ENSG00000012048 BRCA1 prostate glandular cells Medium Enhanced P38398 +ENSG00000012048 BRCA1 seminal vesicle glandular cells Medium Enhanced P38398 +ENSG00000012048 BRCA1 testis cells in seminiferous ducts Medium Enhanced P38398 +ENSG00000012048 BRCA1 testis Leydig cells Medium Enhanced P38398 +ENSG00000012061 ERCC1 epididymis glandular cells Medium Enhanced P07992 +ENSG00000012061 ERCC1 prostate glandular cells Low Enhanced P07992 +ENSG00000012061 ERCC1 seminal vesicle glandular cells Medium Enhanced P07992 +ENSG00000012061 ERCC1 testis cells in seminiferous ducts Medium Enhanced P07992 +ENSG00000012061 ERCC1 testis Leydig cells High Enhanced P07992 +ENSG00000012223 LTF epididymis glandular cells Medium Enhanced P02788 +ENSG00000012223 LTF prostate glandular cells Medium Enhanced P02788 +ENSG00000012660 ELOVL5 epididymis glandular cells Medium Enhanced Q9NYP7 +ENSG00000012660 ELOVL5 prostate glandular cells High Enhanced Q9NYP7 +ENSG00000012660 ELOVL5 seminal vesicle glandular cells High Enhanced Q9NYP7 +ENSG00000012660 ELOVL5 testis cells in seminiferous ducts Medium Enhanced Q9NYP7 +ENSG00000012660 ELOVL5 testis Leydig cells Medium Enhanced Q9NYP7 +ENSG00000012779 ALOX5 seminal vesicle glandular cells Low Enhanced NA +ENSG00000013297 CLDN11 testis sertoli cells High Enhanced O75508 +ENSG00000013364 MVP epididymis glandular cells Low Enhanced Q14764 +ENSG00000013364 MVP seminal vesicle glandular cells Low Enhanced Q14764 +ENSG00000013364 MVP testis cells in seminiferous ducts Medium Enhanced Q14764 +ENSG00000013364 MVP testis Leydig cells High Enhanced Q14764 +ENSG00000013375 PGM3 prostate glandular cells High Enhanced O95394 +ENSG00000013375 PGM3 seminal vesicle glandular cells Low Enhanced O95394 +ENSG00000013375 PGM3 testis cells in seminiferous ducts Medium Enhanced O95394 +ENSG00000013375 PGM3 testis Leydig cells Medium Enhanced O95394 +ENSG00000013503 POLR3B epididymis glandular cells Medium Supported Q9NW08 +ENSG00000013503 POLR3B prostate glandular cells Medium Supported Q9NW08 +ENSG00000013503 POLR3B seminal vesicle glandular cells High Supported Q9NW08 +ENSG00000013503 POLR3B testis cells in seminiferous ducts Medium Supported Q9NW08 +ENSG00000013503 POLR3B testis Leydig cells High Supported Q9NW08 +ENSG00000013573 DDX11 epididymis glandular cells Medium Supported Q96FC9 +ENSG00000013573 DDX11 prostate glandular cells Low Supported Q96FC9 +ENSG00000013573 DDX11 seminal vesicle glandular cells Low Supported Q96FC9 +ENSG00000013573 DDX11 testis cells in seminiferous ducts Medium Supported Q96FC9 +ENSG00000013573 DDX11 testis Leydig cells Medium Supported Q96FC9 +ENSG00000013588 GPRC5A epididymis glandular cells Low Enhanced Q8NFJ5 +ENSG00000013810 TACC3 testis cells in seminiferous ducts High Enhanced Q9Y6A5 +ENSG00000014123 UFL1 epididymis glandular cells Medium Enhanced O94874 +ENSG00000014123 UFL1 prostate glandular cells Medium Enhanced O94874 +ENSG00000014123 UFL1 seminal vesicle glandular cells Medium Enhanced O94874 +ENSG00000014123 UFL1 testis cells in seminiferous ducts Medium Enhanced O94874 +ENSG00000014123 UFL1 testis Leydig cells Medium Enhanced O94874 +ENSG00000014138 POLA2 epididymis glandular cells Medium Enhanced Q14181 +ENSG00000014138 POLA2 prostate glandular cells Low Enhanced Q14181 +ENSG00000014138 POLA2 seminal vesicle glandular cells Medium Enhanced Q14181 +ENSG00000014138 POLA2 testis cells in seminiferous ducts Medium Enhanced Q14181 +ENSG00000014138 POLA2 testis Leydig cells Medium Enhanced Q14181 +ENSG00000014216 CAPN1 epididymis glandular cells High Enhanced P07384 +ENSG00000014216 CAPN1 prostate glandular cells High Enhanced P07384 +ENSG00000014216 CAPN1 seminal vesicle glandular cells High Enhanced P07384 +ENSG00000014216 CAPN1 testis cells in seminiferous ducts Low Enhanced P07384 +ENSG00000014216 CAPN1 testis Leydig cells Medium Enhanced P07384 +ENSG00000014257 ACPP prostate glandular cells High Enhanced P15309 +ENSG00000015153 YAF2 epididymis glandular cells Medium Enhanced Q8IY57 +ENSG00000015153 YAF2 prostate glandular cells Medium Enhanced Q8IY57 +ENSG00000015153 YAF2 seminal vesicle glandular cells Medium Enhanced Q8IY57 +ENSG00000015153 YAF2 testis cells in seminiferous ducts Medium Enhanced Q8IY57 +ENSG00000015153 YAF2 testis Leydig cells High Enhanced Q8IY57 +ENSG00000015285 WAS testis cells in seminiferous ducts Low Enhanced P42768 +ENSG00000015413 DPEP1 testis Leydig cells Medium Enhanced P16444 +ENSG00000015475 BID epididymis glandular cells Low Enhanced P55957 +ENSG00000015475 BID prostate glandular cells Low Enhanced P55957 +ENSG00000015475 BID seminal vesicle glandular cells Low Enhanced P55957 +ENSG00000015475 BID testis cells in seminiferous ducts Low Enhanced P55957 +ENSG00000015479 MATR3 epididymis glandular cells High Enhanced P43243 +ENSG00000015479 MATR3 prostate glandular cells High Enhanced P43243 +ENSG00000015479 MATR3 seminal vesicle glandular cells High Enhanced P43243 +ENSG00000015479 MATR3 testis cells in seminiferous ducts High Enhanced P43243 +ENSG00000015479 MATR3 testis Leydig cells High Enhanced P43243 +ENSG00000015676 NUDCD3 epididymis glandular cells Medium Enhanced Q8IVD9 +ENSG00000015676 NUDCD3 prostate glandular cells Medium Enhanced Q8IVD9 +ENSG00000015676 NUDCD3 seminal vesicle glandular cells Low Enhanced Q8IVD9 +ENSG00000015676 NUDCD3 testis cells in seminiferous ducts High Enhanced Q8IVD9 +ENSG00000015676 NUDCD3 testis Leydig cells Medium Enhanced Q8IVD9 +ENSG00000016391 CHDH prostate glandular cells Medium Enhanced Q8NE62 +ENSG00000017260 ATP2C1 epididymis glandular cells Medium Supported P98194 +ENSG00000017260 ATP2C1 prostate glandular cells Low Supported P98194 +ENSG00000017260 ATP2C1 seminal vesicle glandular cells Medium Supported P98194 +ENSG00000017260 ATP2C1 testis cells in seminiferous ducts Low Supported P98194 +ENSG00000017260 ATP2C1 testis Leydig cells Medium Supported P98194 +ENSG00000018189 RUFY3 epididymis glandular cells Medium Enhanced Q7L099 +ENSG00000018189 RUFY3 seminal vesicle glandular cells Medium Enhanced Q7L099 +ENSG00000018189 RUFY3 testis cells in seminiferous ducts Medium Enhanced Q7L099 +ENSG00000018189 RUFY3 testis Leydig cells High Enhanced Q7L099 +ENSG00000018408 WWTR1 epididymis glandular cells High Enhanced Q9GZV5 +ENSG00000018408 WWTR1 prostate glandular cells High Enhanced Q9GZV5 +ENSG00000018408 WWTR1 seminal vesicle glandular cells Medium Enhanced Q9GZV5 +ENSG00000018408 WWTR1 testis cells in seminiferous ducts High Enhanced Q9GZV5 +ENSG00000018408 WWTR1 testis Leydig cells Medium Enhanced Q9GZV5 +ENSG00000018510 AGPS epididymis glandular cells Medium Supported O00116 +ENSG00000018510 AGPS seminal vesicle glandular cells Medium Supported O00116 +ENSG00000018510 AGPS testis cells in seminiferous ducts Low Supported O00116 +ENSG00000019102 VSIG2 epididymis glandular cells Low Enhanced Q96IQ7 +ENSG00000019102 VSIG2 prostate glandular cells Medium Enhanced Q96IQ7 +ENSG00000019102 VSIG2 seminal vesicle glandular cells Medium Enhanced Q96IQ7 +ENSG00000019102 VSIG2 testis cells in seminiferous ducts Low Enhanced Q96IQ7 +ENSG00000019549 SNAI2 epididymis glandular cells High Supported O43623 +ENSG00000019549 SNAI2 prostate glandular cells Medium Supported O43623 +ENSG00000019549 SNAI2 seminal vesicle glandular cells Medium Supported O43623 +ENSG00000019549 SNAI2 testis cells in seminiferous ducts Medium Supported O43623 +ENSG00000019549 SNAI2 testis Leydig cells Medium Supported O43623 +ENSG00000019582 CD74 testis Leydig cells Low Enhanced P04233 +ENSG00000020922 MRE11 epididymis glandular cells High Supported P49959 +ENSG00000020922 MRE11 prostate glandular cells High Supported P49959 +ENSG00000020922 MRE11 seminal vesicle glandular cells High Supported P49959 +ENSG00000020922 MRE11 testis cells in seminiferous ducts High Supported P49959 +ENSG00000020922 MRE11 testis Leydig cells High Supported P49959 +ENSG00000023191 RNH1 epididymis glandular cells Medium Enhanced E9PIK5 +ENSG00000023191 RNH1 prostate glandular cells Medium Enhanced E9PIK5 +ENSG00000023191 RNH1 seminal vesicle glandular cells Medium Enhanced E9PIK5 +ENSG00000023191 RNH1 testis cells in seminiferous ducts Medium Enhanced E9PIK5 +ENSG00000023191 RNH1 testis Leydig cells Low Enhanced E9PIK5 +ENSG00000023318 ERP44 epididymis glandular cells Medium Supported Q9BS26 +ENSG00000023318 ERP44 prostate glandular cells Medium Supported Q9BS26 +ENSG00000023318 ERP44 seminal vesicle glandular cells Medium Supported Q9BS26 +ENSG00000023318 ERP44 testis cells in seminiferous ducts Medium Supported Q9BS26 +ENSG00000023318 ERP44 testis Leydig cells Low Supported Q9BS26 +ENSG00000023330 ALAS1 epididymis glandular cells Medium Enhanced P13196 +ENSG00000023330 ALAS1 prostate glandular cells Medium Enhanced P13196 +ENSG00000023330 ALAS1 seminal vesicle glandular cells High Enhanced P13196 +ENSG00000023330 ALAS1 testis cells in seminiferous ducts High Enhanced P13196 +ENSG00000023330 ALAS1 testis Leydig cells High Enhanced P13196 +ENSG00000023445 BIRC3 seminal vesicle glandular cells Medium Enhanced Q13489 +ENSG00000023445 BIRC3 testis cells in seminiferous ducts Medium Enhanced Q13489 +ENSG00000023445 BIRC3 testis Leydig cells Low Enhanced Q13489 +ENSG00000023516 AKAP11 epididymis glandular cells High Enhanced Q9UKA4 +ENSG00000023516 AKAP11 prostate glandular cells Medium Enhanced Q9UKA4 +ENSG00000023516 AKAP11 seminal vesicle glandular cells Low Enhanced Q9UKA4 +ENSG00000023516 AKAP11 testis cells in seminiferous ducts Medium Enhanced Q9UKA4 +ENSG00000023516 AKAP11 testis Leydig cells Medium Enhanced Q9UKA4 +ENSG00000023572 GLRX2 epididymis glandular cells Medium Supported Q9NS18 +ENSG00000023572 GLRX2 prostate glandular cells High Supported Q9NS18 +ENSG00000023572 GLRX2 seminal vesicle glandular cells Low Supported Q9NS18 +ENSG00000023572 GLRX2 testis cells in seminiferous ducts Medium Supported Q9NS18 +ENSG00000023572 GLRX2 testis Leydig cells Medium Supported Q9NS18 +ENSG00000023839 ABCC2 epididymis glandular cells Low Enhanced Q92887 +ENSG00000023839 ABCC2 prostate glandular cells Medium Enhanced Q92887 +ENSG00000023839 ABCC2 testis cells in seminiferous ducts Medium Enhanced Q92887 +ENSG00000023839 ABCC2 testis Leydig cells Low Enhanced Q92887 +ENSG00000025423 HSD17B6 epididymis glandular cells Low Enhanced O14756 +ENSG00000025423 HSD17B6 prostate glandular cells Low Enhanced O14756 +ENSG00000025423 HSD17B6 seminal vesicle glandular cells Medium Enhanced O14756 +ENSG00000025423 HSD17B6 testis cells in seminiferous ducts Medium Enhanced O14756 +ENSG00000025423 HSD17B6 testis Leydig cells Medium Enhanced O14756 +ENSG00000025708 TYMP prostate glandular cells Low Enhanced P19971 +ENSG00000025708 TYMP seminal vesicle glandular cells Low Enhanced P19971 +ENSG00000025770 NCAPH2 epididymis glandular cells Low Enhanced Q6IBW4 +ENSG00000025770 NCAPH2 prostate glandular cells Low Enhanced Q6IBW4 +ENSG00000025770 NCAPH2 seminal vesicle glandular cells Low Enhanced Q6IBW4 +ENSG00000025770 NCAPH2 testis cells in seminiferous ducts High Enhanced Q6IBW4 +ENSG00000025770 NCAPH2 testis Leydig cells Low Enhanced Q6IBW4 +ENSG00000025772 TOMM34 epididymis glandular cells Medium Enhanced Q15785 +ENSG00000025772 TOMM34 prostate glandular cells Low Enhanced Q15785 +ENSG00000025772 TOMM34 testis cells in seminiferous ducts High Enhanced Q15785 +ENSG00000025772 TOMM34 testis Leydig cells Low Enhanced Q15785 +ENSG00000025796 SEC63 epididymis glandular cells Medium Enhanced Q9UGP8 +ENSG00000025796 SEC63 prostate glandular cells Medium Enhanced Q9UGP8 +ENSG00000025796 SEC63 seminal vesicle glandular cells Medium Enhanced Q9UGP8 +ENSG00000025796 SEC63 testis cells in seminiferous ducts High Enhanced Q9UGP8 +ENSG00000025796 SEC63 testis Leydig cells High Enhanced Q9UGP8 +ENSG00000025800 KPNA6 epididymis glandular cells High Supported O60684 +ENSG00000025800 KPNA6 prostate glandular cells Medium Supported O60684 +ENSG00000025800 KPNA6 seminal vesicle glandular cells High Supported O60684 +ENSG00000025800 KPNA6 testis cells in seminiferous ducts High Supported O60684 +ENSG00000025800 KPNA6 testis Leydig cells High Supported O60684 +ENSG00000026025 VIM epididymis glandular cells High Enhanced P08670 +ENSG00000026025 VIM seminal vesicle glandular cells High Enhanced P08670 +ENSG00000026025 VIM testis cells in seminiferous ducts High Enhanced P08670 +ENSG00000026025 VIM testis Leydig cells High Enhanced P08670 +ENSG00000026103 FAS epididymis glandular cells Low Enhanced P25445 +ENSG00000026103 FAS prostate glandular cells Low Enhanced P25445 +ENSG00000026103 FAS seminal vesicle glandular cells Medium Enhanced P25445 +ENSG00000026103 FAS testis Leydig cells High Enhanced P25445 +ENSG00000026508 CD44 epididymis glandular cells Medium Enhanced P16070 +ENSG00000026508 CD44 prostate glandular cells High Enhanced P16070 +ENSG00000026508 CD44 seminal vesicle glandular cells Low Enhanced P16070 +ENSG00000026508 CD44 testis Leydig cells Low Enhanced P16070 +ENSG00000027847 B4GALT7 epididymis glandular cells High Supported Q9UBV7 +ENSG00000027847 B4GALT7 prostate glandular cells Low Supported Q9UBV7 +ENSG00000027847 B4GALT7 seminal vesicle glandular cells Medium Supported Q9UBV7 +ENSG00000027847 B4GALT7 testis cells in seminiferous ducts Low Supported Q9UBV7 +ENSG00000027847 B4GALT7 testis Leydig cells Medium Supported Q9UBV7 +ENSG00000028839 TBPL1 epididymis glandular cells Low Enhanced P62380 +ENSG00000028839 TBPL1 prostate glandular cells Low Enhanced P62380 +ENSG00000028839 TBPL1 seminal vesicle glandular cells Low Enhanced P62380 +ENSG00000028839 TBPL1 testis elongated or late spermatids Low Enhanced P62380 +ENSG00000028839 TBPL1 testis Leydig cells Low Enhanced P62380 +ENSG00000028839 TBPL1 testis pachytene spermatocytes High Enhanced P62380 +ENSG00000028839 TBPL1 testis preleptotene spermatocytes High Enhanced P62380 +ENSG00000028839 TBPL1 testis round or early spermatids Medium Enhanced P62380 +ENSG00000028839 TBPL1 testis spermatogonia Medium Enhanced P62380 +ENSG00000029363 BCLAF1 epididymis glandular cells High Enhanced Q9NYF8 +ENSG00000029363 BCLAF1 prostate glandular cells High Enhanced Q9NYF8 +ENSG00000029363 BCLAF1 seminal vesicle glandular cells High Enhanced Q9NYF8 +ENSG00000029363 BCLAF1 testis cells in seminiferous ducts High Enhanced Q9NYF8 +ENSG00000029363 BCLAF1 testis Leydig cells High Enhanced Q9NYF8 +ENSG00000029364 SLC39A9 epididymis glandular cells High Enhanced Q9NUM3 +ENSG00000029364 SLC39A9 prostate glandular cells High Enhanced Q9NUM3 +ENSG00000029364 SLC39A9 seminal vesicle glandular cells High Enhanced Q9NUM3 +ENSG00000029364 SLC39A9 testis cells in seminiferous ducts Medium Enhanced Q9NUM3 +ENSG00000029364 SLC39A9 testis Leydig cells High Enhanced Q9NUM3 +ENSG00000029725 RABEP1 epididymis glandular cells Medium Enhanced Q15276 +ENSG00000029725 RABEP1 prostate glandular cells Medium Enhanced Q15276 +ENSG00000029725 RABEP1 seminal vesicle glandular cells Medium Enhanced Q15276 +ENSG00000029725 RABEP1 testis cells in seminiferous ducts Medium Enhanced Q15276 +ENSG00000029725 RABEP1 testis Leydig cells Medium Enhanced Q15276 +ENSG00000029993 HMGB3 epididymis glandular cells Low Enhanced O15347 +ENSG00000029993 HMGB3 testis cells in seminiferous ducts Low Enhanced O15347 +ENSG00000030110 BAK1 epididymis glandular cells Low Enhanced Q16611 +ENSG00000030110 BAK1 prostate glandular cells Low Enhanced Q16611 +ENSG00000030110 BAK1 seminal vesicle glandular cells Low Enhanced Q16611 +ENSG00000030110 BAK1 testis cells in seminiferous ducts Medium Enhanced Q16611 +ENSG00000030110 BAK1 testis Leydig cells Medium Enhanced Q16611 +ENSG00000031823 RANBP3 epididymis glandular cells High Enhanced Q9H6Z4 +ENSG00000031823 RANBP3 prostate glandular cells Medium Enhanced Q9H6Z4 +ENSG00000031823 RANBP3 seminal vesicle glandular cells Medium Enhanced Q9H6Z4 +ENSG00000031823 RANBP3 testis cells in seminiferous ducts High Enhanced Q9H6Z4 +ENSG00000031823 RANBP3 testis Leydig cells High Enhanced Q9H6Z4 +ENSG00000033030 ZCCHC8 epididymis glandular cells High Supported Q6NZY4 +ENSG00000033030 ZCCHC8 prostate glandular cells Medium Supported Q6NZY4 +ENSG00000033030 ZCCHC8 seminal vesicle glandular cells High Supported Q6NZY4 +ENSG00000033030 ZCCHC8 testis cells in seminiferous ducts High Supported Q6NZY4 +ENSG00000033030 ZCCHC8 testis Leydig cells High Supported Q6NZY4 +ENSG00000033050 ABCF2 prostate glandular cells Low Enhanced Q9UG63 +ENSG00000033050 ABCF2 seminal vesicle glandular cells Medium Enhanced Q9UG63 +ENSG00000033050 ABCF2 testis cells in seminiferous ducts Medium Enhanced Q9UG63 +ENSG00000033170 FUT8 epididymis glandular cells Medium Enhanced Q9BYC5 +ENSG00000033170 FUT8 prostate glandular cells Medium Enhanced Q9BYC5 +ENSG00000033170 FUT8 seminal vesicle glandular cells High Enhanced Q9BYC5 +ENSG00000033170 FUT8 testis cells in seminiferous ducts High Enhanced Q9BYC5 +ENSG00000033170 FUT8 testis Leydig cells Medium Enhanced Q9BYC5 +ENSG00000033327 GAB2 epididymis glandular cells Medium Enhanced Q9UQC2 +ENSG00000033327 GAB2 prostate glandular cells Medium Enhanced Q9UQC2 +ENSG00000033327 GAB2 seminal vesicle glandular cells Medium Enhanced Q9UQC2 +ENSG00000033327 GAB2 testis cells in seminiferous ducts Medium Enhanced Q9UQC2 +ENSG00000033327 GAB2 testis Leydig cells Medium Enhanced Q9UQC2 +ENSG00000033627 ATP6V0A1 epididymis glandular cells Medium Enhanced Q93050 +ENSG00000033627 ATP6V0A1 prostate glandular cells High Enhanced Q93050 +ENSG00000033627 ATP6V0A1 seminal vesicle glandular cells Medium Enhanced Q93050 +ENSG00000033627 ATP6V0A1 testis cells in seminiferous ducts Medium Enhanced Q93050 +ENSG00000033627 ATP6V0A1 testis Leydig cells Medium Enhanced Q93050 +ENSG00000033800 PIAS1 epididymis glandular cells High Supported O75925 +ENSG00000033800 PIAS1 prostate glandular cells Medium Supported O75925 +ENSG00000033800 PIAS1 seminal vesicle glandular cells High Supported O75925 +ENSG00000033800 PIAS1 testis cells in seminiferous ducts High Supported O75925 +ENSG00000033800 PIAS1 testis Leydig cells Medium Supported O75925 +ENSG00000034239 EFCAB1 testis elongated or late spermatids High Enhanced Q9HAE3 +ENSG00000034239 EFCAB1 testis Leydig cells Low Enhanced Q9HAE3 +ENSG00000034239 EFCAB1 testis round or early spermatids High Enhanced Q9HAE3 +ENSG00000034533 ASTE1 epididymis glandular cells Medium Enhanced Q2TB18 +ENSG00000034533 ASTE1 prostate glandular cells High Enhanced Q2TB18 +ENSG00000034533 ASTE1 seminal vesicle glandular cells High Enhanced Q2TB18 +ENSG00000034533 ASTE1 testis Leydig cells Low Enhanced Q2TB18 +ENSG00000034693 PEX3 epididymis glandular cells Medium Enhanced P56589 +ENSG00000034693 PEX3 prostate glandular cells Medium Enhanced P56589 +ENSG00000034693 PEX3 seminal vesicle glandular cells Medium Enhanced P56589 +ENSG00000034693 PEX3 testis cells in seminiferous ducts High Enhanced P56589 +ENSG00000034693 PEX3 testis Leydig cells High Enhanced P56589 +ENSG00000035141 FAM136A epididymis glandular cells Medium Enhanced Q96C01 +ENSG00000035141 FAM136A prostate glandular cells Medium Enhanced Q96C01 +ENSG00000035141 FAM136A seminal vesicle glandular cells Medium Enhanced Q96C01 +ENSG00000035141 FAM136A testis cells in seminiferous ducts Medium Enhanced Q96C01 +ENSG00000035141 FAM136A testis Leydig cells Medium Enhanced Q96C01 +ENSG00000035403 VCL epididymis glandular cells Medium Enhanced P18206 +ENSG00000035403 VCL prostate glandular cells Low Enhanced P18206 +ENSG00000035403 VCL seminal vesicle glandular cells Medium Enhanced P18206 +ENSG00000035403 VCL testis cells in seminiferous ducts High Enhanced P18206 +ENSG00000035403 VCL testis Leydig cells Low Enhanced P18206 +ENSG00000035687 ADSS epididymis glandular cells Medium Enhanced P30520 +ENSG00000035687 ADSS prostate glandular cells Medium Enhanced P30520 +ENSG00000035687 ADSS seminal vesicle glandular cells Medium Enhanced P30520 +ENSG00000035687 ADSS testis cells in seminiferous ducts Medium Enhanced P30520 +ENSG00000035687 ADSS testis Leydig cells Medium Enhanced P30520 +ENSG00000035928 RFC1 epididymis glandular cells Low Supported P35251 +ENSG00000035928 RFC1 prostate glandular cells Low Supported P35251 +ENSG00000035928 RFC1 seminal vesicle glandular cells Medium Supported P35251 +ENSG00000035928 RFC1 testis cells in seminiferous ducts Low Supported P35251 +ENSG00000035928 RFC1 testis Leydig cells Low Supported P35251 +ENSG00000036257 CUL3 epididymis glandular cells High Supported Q13618 +ENSG00000036257 CUL3 prostate glandular cells Medium Supported Q13618 +ENSG00000036257 CUL3 seminal vesicle glandular cells High Supported Q13618 +ENSG00000036257 CUL3 testis cells in seminiferous ducts High Supported Q13618 +ENSG00000036257 CUL3 testis Leydig cells Low Supported Q13618 +ENSG00000036448 MYOM2 epididymis glandular cells Low Enhanced E7EWH9 +ENSG00000036448 MYOM2 prostate glandular cells Medium Enhanced E7EWH9 +ENSG00000036448 MYOM2 seminal vesicle glandular cells Low Enhanced E7EWH9 +ENSG00000036448 MYOM2 testis cells in seminiferous ducts Low Enhanced E7EWH9 +ENSG00000036448 MYOM2 testis Leydig cells Low Enhanced E7EWH9 +ENSG00000037474 NSUN2 epididymis glandular cells High Enhanced Q08J23 +ENSG00000037474 NSUN2 prostate glandular cells Medium Enhanced Q08J23 +ENSG00000037474 NSUN2 seminal vesicle glandular cells Medium Enhanced Q08J23 +ENSG00000037474 NSUN2 testis cells in seminiferous ducts High Enhanced Q08J23 +ENSG00000037474 NSUN2 testis Leydig cells High Enhanced Q08J23 +ENSG00000038002 AGA epididymis glandular cells High Enhanced P20933 +ENSG00000038002 AGA prostate glandular cells High Enhanced P20933 +ENSG00000038002 AGA seminal vesicle glandular cells High Enhanced P20933 +ENSG00000038002 AGA testis cells in seminiferous ducts High Enhanced P20933 +ENSG00000038002 AGA testis Leydig cells High Enhanced P20933 +ENSG00000038358 EDC4 epididymis glandular cells High Supported Q6P2E9 +ENSG00000038358 EDC4 prostate glandular cells Medium Supported Q6P2E9 +ENSG00000038358 EDC4 seminal vesicle glandular cells Medium Supported Q6P2E9 +ENSG00000038358 EDC4 testis cells in seminiferous ducts Medium Supported Q6P2E9 +ENSG00000038358 EDC4 testis Leydig cells Low Supported Q6P2E9 +ENSG00000038382 TRIO epididymis glandular cells Medium Supported O75962 +ENSG00000038382 TRIO prostate glandular cells Medium Supported O75962 +ENSG00000038382 TRIO testis cells in seminiferous ducts Medium Supported O75962 +ENSG00000038382 TRIO testis Leydig cells Medium Supported O75962 +ENSG00000038427 VCAN prostate glandular cells Low Enhanced P13611 +ENSG00000038427 VCAN testis cells in seminiferous ducts Low Enhanced P13611 +ENSG00000039068 CDH1 epididymis glandular cells High Enhanced P12830 +ENSG00000039068 CDH1 prostate glandular cells High Enhanced P12830 +ENSG00000039068 CDH1 seminal vesicle glandular cells High Enhanced P12830 +ENSG00000039123 SKIV2L2 epididymis glandular cells Medium Supported P42285 +ENSG00000039123 SKIV2L2 prostate glandular cells Medium Supported P42285 +ENSG00000039123 SKIV2L2 seminal vesicle glandular cells High Supported P42285 +ENSG00000039123 SKIV2L2 testis cells in seminiferous ducts High Supported P42285 +ENSG00000039123 SKIV2L2 testis Leydig cells Medium Supported P42285 +ENSG00000039319 ZFYVE16 epididymis glandular cells Low Supported Q7Z3T8 +ENSG00000039319 ZFYVE16 prostate glandular cells Medium Supported Q7Z3T8 +ENSG00000039319 ZFYVE16 seminal vesicle glandular cells Low Supported Q7Z3T8 +ENSG00000039319 ZFYVE16 testis cells in seminiferous ducts Medium Supported Q7Z3T8 +ENSG00000039319 ZFYVE16 testis Leydig cells Low Supported Q7Z3T8 +ENSG00000039560 RAI14 epididymis glandular cells Medium Supported Q9P0K7 +ENSG00000039560 RAI14 prostate glandular cells Medium Supported Q9P0K7 +ENSG00000039560 RAI14 seminal vesicle glandular cells Medium Supported Q9P0K7 +ENSG00000039560 RAI14 testis cells in seminiferous ducts Medium Supported Q9P0K7 +ENSG00000039560 RAI14 testis Leydig cells Low Supported Q9P0K7 +ENSG00000039600 SOX30 testis Leydig cells Low Enhanced O94993 +ENSG00000039600 SOX30 testis pachytene spermatocytes Low Enhanced O94993 +ENSG00000039600 SOX30 testis preleptotene spermatocytes Low Enhanced O94993 +ENSG00000039600 SOX30 testis round or early spermatids High Enhanced O94993 +ENSG00000039650 PNKP epididymis glandular cells High Supported Q96T60 +ENSG00000039650 PNKP prostate glandular cells Medium Supported Q96T60 +ENSG00000039650 PNKP seminal vesicle glandular cells High Supported Q96T60 +ENSG00000039650 PNKP testis cells in seminiferous ducts High Supported Q96T60 +ENSG00000039650 PNKP testis Leydig cells Medium Supported Q96T60 +ENSG00000040275 SPDL1 epididymis glandular cells Medium Enhanced Q96EA4 +ENSG00000040275 SPDL1 prostate glandular cells Low Enhanced Q96EA4 +ENSG00000040275 SPDL1 seminal vesicle glandular cells Medium Enhanced Q96EA4 +ENSG00000040275 SPDL1 testis cells in seminiferous ducts High Enhanced Q96EA4 +ENSG00000040275 SPDL1 testis Leydig cells Medium Enhanced Q96EA4 +ENSG00000041353 RAB27B epididymis glandular cells Low Enhanced O00194 +ENSG00000041353 RAB27B prostate glandular cells High Enhanced O00194 +ENSG00000041353 RAB27B testis Leydig cells Low Enhanced O00194 +ENSG00000041357 PSMA4 epididymis glandular cells Medium Supported P25789 +ENSG00000041357 PSMA4 prostate glandular cells Medium Supported P25789 +ENSG00000041357 PSMA4 seminal vesicle glandular cells Low Supported P25789 +ENSG00000041357 PSMA4 testis cells in seminiferous ducts Medium Supported P25789 +ENSG00000041357 PSMA4 testis Leydig cells Medium Supported P25789 +ENSG00000041880 PARP3 epididymis glandular cells High Supported Q9Y6F1 +ENSG00000041880 PARP3 prostate glandular cells Medium Supported Q9Y6F1 +ENSG00000041880 PARP3 seminal vesicle glandular cells High Supported Q9Y6F1 +ENSG00000041880 PARP3 testis cells in seminiferous ducts High Supported Q9Y6F1 +ENSG00000041880 PARP3 testis Leydig cells Medium Supported Q9Y6F1 +ENSG00000042317 SPATA7 testis cells in seminiferous ducts Medium Enhanced Q9P0W8 +ENSG00000042813 ZPBP testis elongated or late spermatids High Enhanced Q9BS86 +ENSG00000042813 ZPBP testis round or early spermatids High Enhanced Q9BS86 +ENSG00000042980 ADAM28 epididymis glandular cells High Enhanced Q9UKQ2 +ENSG00000042980 ADAM28 seminal vesicle glandular cells Medium Enhanced Q9UKQ2 +ENSG00000043462 LCP2 epididymis glandular cells Low Enhanced Q13094 +ENSG00000043462 LCP2 prostate glandular cells Low Enhanced Q13094 +ENSG00000043462 LCP2 seminal vesicle glandular cells Low Enhanced Q13094 +ENSG00000043462 LCP2 testis cells in seminiferous ducts Low Enhanced Q13094 +ENSG00000043462 LCP2 testis Leydig cells Low Enhanced Q13094 +ENSG00000044574 HSPA5 epididymis glandular cells Medium Enhanced P11021 +ENSG00000044574 HSPA5 prostate glandular cells Medium Enhanced P11021 +ENSG00000044574 HSPA5 seminal vesicle glandular cells Medium Enhanced P11021 +ENSG00000044574 HSPA5 testis cells in seminiferous ducts High Enhanced P11021 +ENSG00000044574 HSPA5 testis Leydig cells Medium Enhanced P11021 +ENSG00000046604 DSG2 epididymis glandular cells Medium Enhanced Q14126 +ENSG00000046604 DSG2 prostate glandular cells High Enhanced Q14126 +ENSG00000046604 DSG2 seminal vesicle glandular cells Low Enhanced Q14126 +ENSG00000046604 DSG2 testis cells in seminiferous ducts Low Enhanced Q14126 +ENSG00000046774 MAGEC2 testis pachytene spermatocytes High Enhanced Q9UBF1 +ENSG00000046774 MAGEC2 testis preleptotene spermatocytes High Enhanced Q9UBF1 +ENSG00000046774 MAGEC2 testis round or early spermatids Low Enhanced Q9UBF1 +ENSG00000046774 MAGEC2 testis spermatogonia Medium Enhanced Q9UBF1 +ENSG00000046889 PREX2 epididymis glandular cells Low Enhanced Q70Z35 +ENSG00000046889 PREX2 prostate glandular cells Low Enhanced Q70Z35 +ENSG00000046889 PREX2 seminal vesicle glandular cells Low Enhanced Q70Z35 +ENSG00000046889 PREX2 testis Leydig cells Low Enhanced Q70Z35 +ENSG00000047056 WDR37 epididymis glandular cells Medium Enhanced Q9Y2I8 +ENSG00000047056 WDR37 prostate glandular cells Medium Enhanced Q9Y2I8 +ENSG00000047056 WDR37 seminal vesicle glandular cells Medium Enhanced Q9Y2I8 +ENSG00000047056 WDR37 testis cells in seminiferous ducts Medium Enhanced Q9Y2I8 +ENSG00000047056 WDR37 testis Leydig cells Medium Enhanced Q9Y2I8 +ENSG00000047315 POLR2B epididymis glandular cells High Supported P30876 +ENSG00000047315 POLR2B prostate glandular cells Medium Supported P30876 +ENSG00000047315 POLR2B seminal vesicle glandular cells Medium Supported P30876 +ENSG00000047315 POLR2B testis cells in seminiferous ducts Medium Supported P30876 +ENSG00000047410 TPR epididymis glandular cells High Enhanced P12270 +ENSG00000047410 TPR prostate glandular cells Medium Enhanced P12270 +ENSG00000047410 TPR seminal vesicle glandular cells High Enhanced P12270 +ENSG00000047410 TPR testis cells in seminiferous ducts High Enhanced P12270 +ENSG00000047410 TPR testis Leydig cells Medium Enhanced P12270 +ENSG00000047578 KIAA0556 epididymis glandular cells Medium Enhanced O60303 +ENSG00000047578 KIAA0556 prostate glandular cells Medium Enhanced O60303 +ENSG00000047578 KIAA0556 seminal vesicle glandular cells Medium Enhanced O60303 +ENSG00000047578 KIAA0556 testis cells in seminiferous ducts Medium Enhanced O60303 +ENSG00000047578 KIAA0556 testis Leydig cells Medium Enhanced O60303 +ENSG00000047579 DTNBP1 epididymis glandular cells Medium Enhanced Q96EV8 +ENSG00000047579 DTNBP1 prostate glandular cells High Enhanced Q96EV8 +ENSG00000047579 DTNBP1 seminal vesicle glandular cells Medium Enhanced Q96EV8 +ENSG00000047579 DTNBP1 testis cells in seminiferous ducts Low Enhanced Q96EV8 +ENSG00000047579 DTNBP1 testis Leydig cells Medium Enhanced Q96EV8 +ENSG00000047634 SCML1 testis cells in seminiferous ducts High Enhanced Q9UN30 +ENSG00000047648 ARHGAP6 epididymis glandular cells Medium Enhanced O43182 +ENSG00000047648 ARHGAP6 prostate glandular cells Medium Enhanced O43182 +ENSG00000047648 ARHGAP6 seminal vesicle glandular cells Medium Enhanced O43182 +ENSG00000047648 ARHGAP6 testis cells in seminiferous ducts High Enhanced O43182 +ENSG00000047648 ARHGAP6 testis Leydig cells High Enhanced O43182 +ENSG00000047662 FAM184B testis cells in seminiferous ducts Low Enhanced Q9ULE4 +ENSG00000047849 MAP4 epididymis glandular cells High Enhanced P27816 +ENSG00000047849 MAP4 prostate glandular cells Low Enhanced P27816 +ENSG00000047849 MAP4 seminal vesicle glandular cells Medium Enhanced P27816 +ENSG00000047849 MAP4 testis cells in seminiferous ducts High Enhanced P27816 +ENSG00000047849 MAP4 testis Leydig cells High Enhanced P27816 +ENSG00000048028 USP28 epididymis glandular cells Medium Enhanced Q96RU2 +ENSG00000048028 USP28 prostate glandular cells Medium Enhanced Q96RU2 +ENSG00000048028 USP28 seminal vesicle glandular cells Medium Enhanced Q96RU2 +ENSG00000048028 USP28 testis cells in seminiferous ducts Medium Enhanced Q96RU2 +ENSG00000048028 USP28 testis Leydig cells Medium Enhanced Q96RU2 +ENSG00000048544 MRPS10 epididymis glandular cells High Enhanced P82664 +ENSG00000048544 MRPS10 prostate glandular cells Medium Enhanced P82664 +ENSG00000048544 MRPS10 seminal vesicle glandular cells High Enhanced P82664 +ENSG00000048544 MRPS10 testis cells in seminiferous ducts High Enhanced P82664 +ENSG00000048544 MRPS10 testis Leydig cells High Enhanced P82664 +ENSG00000048649 RSF1 epididymis glandular cells Medium Enhanced Q96T23 +ENSG00000048649 RSF1 prostate glandular cells Low Enhanced Q96T23 +ENSG00000048649 RSF1 seminal vesicle glandular cells Medium Enhanced Q96T23 +ENSG00000048649 RSF1 testis cells in seminiferous ducts Medium Enhanced Q96T23 +ENSG00000048649 RSF1 testis Leydig cells Medium Enhanced Q96T23 +ENSG00000049768 FOXP3 testis Leydig cells Low Enhanced Q9BZS1 +ENSG00000049860 HEXB epididymis glandular cells High Enhanced P07686 +ENSG00000049860 HEXB prostate glandular cells Medium Enhanced P07686 +ENSG00000049860 HEXB seminal vesicle glandular cells Low Enhanced P07686 +ENSG00000049860 HEXB testis cells in seminiferous ducts Low Enhanced P07686 +ENSG00000049860 HEXB testis Leydig cells Medium Enhanced P07686 +ENSG00000050130 JKAMP epididymis glandular cells Medium Supported Q9P055 +ENSG00000050130 JKAMP prostate glandular cells Medium Supported Q9P055 +ENSG00000050130 JKAMP seminal vesicle glandular cells Medium Supported Q9P055 +ENSG00000050130 JKAMP testis cells in seminiferous ducts High Supported Q9P055 +ENSG00000050130 JKAMP testis Leydig cells Low Supported Q9P055 +ENSG00000050327 ARHGEF5 epididymis glandular cells High Enhanced Q12774 +ENSG00000050327 ARHGEF5 prostate glandular cells Medium Enhanced Q12774 +ENSG00000050327 ARHGEF5 seminal vesicle glandular cells Medium Enhanced Q12774 +ENSG00000050327 ARHGEF5 testis cells in seminiferous ducts Medium Enhanced Q12774 +ENSG00000050327 ARHGEF5 testis Leydig cells Medium Enhanced Q12774 +ENSG00000050344 NFE2L3 prostate glandular cells Medium Enhanced Q9Y4A8 +ENSG00000050344 NFE2L3 testis cells in seminiferous ducts Low Enhanced Q9Y4A8 +ENSG00000050405 LIMA1 epididymis glandular cells High Enhanced Q9UHB6 +ENSG00000050405 LIMA1 prostate glandular cells High Enhanced Q9UHB6 +ENSG00000050405 LIMA1 seminal vesicle glandular cells High Enhanced Q9UHB6 +ENSG00000050405 LIMA1 testis cells in seminiferous ducts Medium Enhanced Q9UHB6 +ENSG00000050405 LIMA1 testis Leydig cells Medium Enhanced Q9UHB6 +ENSG00000050555 LAMC3 seminal vesicle glandular cells Low Enhanced Q9Y6N6 +ENSG00000051180 RAD51 testis elongated or late spermatids Medium Enhanced Q06609 +ENSG00000051180 RAD51 testis Leydig cells Medium Enhanced Q06609 +ENSG00000051180 RAD51 testis pachytene spermatocytes High Enhanced Q06609 +ENSG00000051180 RAD51 testis peritubular cells Low Enhanced Q06609 +ENSG00000051180 RAD51 testis preleptotene spermatocytes High Enhanced Q06609 +ENSG00000051180 RAD51 testis round or early spermatids Medium Enhanced Q06609 +ENSG00000051180 RAD51 testis sertoli cells Medium Enhanced Q06609 +ENSG00000051180 RAD51 testis spermatogonia Low Enhanced Q06609 +ENSG00000052723 SIKE1 epididymis glandular cells Medium Supported Q9BRV8 +ENSG00000052723 SIKE1 prostate glandular cells Medium Supported Q9BRV8 +ENSG00000052723 SIKE1 seminal vesicle glandular cells Medium Supported Q9BRV8 +ENSG00000052723 SIKE1 testis cells in seminiferous ducts Medium Supported Q9BRV8 +ENSG00000052723 SIKE1 testis Leydig cells Medium Supported Q9BRV8 +ENSG00000053371 AKR7A2 epididymis glandular cells Low Enhanced O43488 +ENSG00000053371 AKR7A2 prostate glandular cells Medium Enhanced O43488 +ENSG00000053371 AKR7A2 seminal vesicle glandular cells Medium Enhanced O43488 +ENSG00000053371 AKR7A2 testis cells in seminiferous ducts Medium Enhanced O43488 +ENSG00000053371 AKR7A2 testis Leydig cells Medium Enhanced O43488 +ENSG00000053918 KCNQ1 epididymis glandular cells Medium Enhanced P51787 +ENSG00000053918 KCNQ1 seminal vesicle glandular cells High Enhanced P51787 +ENSG00000053918 KCNQ1 testis cells in seminiferous ducts Low Enhanced P51787 +ENSG00000053918 KCNQ1 testis Leydig cells Low Enhanced P51787 +ENSG00000054118 THRAP3 epididymis glandular cells High Supported Q9Y2W1 +ENSG00000054118 THRAP3 prostate glandular cells High Supported Q9Y2W1 +ENSG00000054118 THRAP3 seminal vesicle glandular cells High Supported Q9Y2W1 +ENSG00000054118 THRAP3 testis cells in seminiferous ducts High Supported Q9Y2W1 +ENSG00000054118 THRAP3 testis Leydig cells High Supported Q9Y2W1 +ENSG00000054598 FOXC1 epididymis glandular cells Medium Enhanced Q12948 +ENSG00000054598 FOXC1 prostate glandular cells Low Enhanced Q12948 +ENSG00000054598 FOXC1 seminal vesicle glandular cells Medium Enhanced Q12948 +ENSG00000054598 FOXC1 testis cells in seminiferous ducts Medium Enhanced Q12948 +ENSG00000054598 FOXC1 testis Leydig cells Medium Enhanced Q12948 +ENSG00000054654 SYNE2 prostate glandular cells Medium Enhanced Q8WXH0 +ENSG00000054654 SYNE2 testis cells in seminiferous ducts Medium Enhanced Q8WXH0 +ENSG00000054654 SYNE2 testis Leydig cells Low Enhanced Q8WXH0 +ENSG00000055044 NOP58 epididymis glandular cells Medium Supported Q9Y2X3 +ENSG00000055044 NOP58 prostate glandular cells Low Supported Q9Y2X3 +ENSG00000055044 NOP58 seminal vesicle glandular cells Medium Supported Q9Y2X3 +ENSG00000055044 NOP58 testis cells in seminiferous ducts Medium Supported Q9Y2X3 +ENSG00000055044 NOP58 testis Leydig cells Medium Supported Q9Y2X3 +ENSG00000055130 CUL1 epididymis glandular cells Low Supported Q13616 +ENSG00000055130 CUL1 prostate glandular cells Low Supported Q13616 +ENSG00000055130 CUL1 seminal vesicle glandular cells Low Supported Q13616 +ENSG00000055130 CUL1 testis cells in seminiferous ducts Medium Supported Q13616 +ENSG00000055130 CUL1 testis Leydig cells Medium Supported Q13616 +ENSG00000055955 ITIH4 epididymis glandular cells Low Enhanced Q14624 +ENSG00000055955 ITIH4 prostate glandular cells Low Enhanced Q14624 +ENSG00000055955 ITIH4 testis Leydig cells Low Enhanced Q14624 +ENSG00000056097 ZFR epididymis glandular cells High Supported Q96KR1 +ENSG00000056097 ZFR prostate glandular cells High Supported Q96KR1 +ENSG00000056097 ZFR seminal vesicle glandular cells High Supported Q96KR1 +ENSG00000056097 ZFR testis cells in seminiferous ducts High Supported Q96KR1 +ENSG00000056097 ZFR testis Leydig cells High Supported Q96KR1 +ENSG00000056277 ZNF280C epididymis glandular cells Medium Enhanced Q8ND82 +ENSG00000056277 ZNF280C prostate glandular cells Low Enhanced Q8ND82 +ENSG00000056277 ZNF280C seminal vesicle glandular cells Low Enhanced Q8ND82 +ENSG00000056277 ZNF280C testis Leydig cells Medium Enhanced Q8ND82 +ENSG00000056277 ZNF280C testis pachytene spermatocytes Medium Enhanced Q8ND82 +ENSG00000056277 ZNF280C testis peritubular cells Medium Enhanced Q8ND82 +ENSG00000056277 ZNF280C testis preleptotene spermatocytes High Enhanced Q8ND82 +ENSG00000056277 ZNF280C testis spermatogonia Medium Enhanced Q8ND82 +ENSG00000056736 IL17RB testis Leydig cells High Supported Q9NRM6 +ENSG00000057252 SOAT1 prostate glandular cells Medium Enhanced P35610 +ENSG00000057252 SOAT1 testis Leydig cells Medium Enhanced P35610 +ENSG00000057294 PKP2 epididymis glandular cells Low Enhanced Q99959 +ENSG00000057294 PKP2 testis cells in seminiferous ducts Medium Enhanced Q99959 +ENSG00000057294 PKP2 testis Leydig cells Medium Enhanced Q99959 +ENSG00000057608 GDI2 epididymis glandular cells Medium Supported P50395 +ENSG00000057608 GDI2 prostate glandular cells Low Supported P50395 +ENSG00000057608 GDI2 seminal vesicle glandular cells Medium Supported P50395 +ENSG00000057608 GDI2 testis cells in seminiferous ducts Medium Supported P50395 +ENSG00000057608 GDI2 testis Leydig cells Medium Supported P50395 +ENSG00000057663 ATG5 epididymis glandular cells Medium Enhanced Q9H1Y0 +ENSG00000057663 ATG5 prostate glandular cells Medium Enhanced Q9H1Y0 +ENSG00000057663 ATG5 seminal vesicle glandular cells Medium Enhanced Q9H1Y0 +ENSG00000057663 ATG5 testis cells in seminiferous ducts Medium Enhanced Q9H1Y0 +ENSG00000057663 ATG5 testis Leydig cells Medium Enhanced Q9H1Y0 +ENSG00000058404 CAMK2B epididymis glandular cells Low Enhanced Q13554 +ENSG00000058668 ATP2B4 epididymis glandular cells Medium Enhanced P23634 +ENSG00000058668 ATP2B4 prostate glandular cells Low Enhanced P23634 +ENSG00000058668 ATP2B4 seminal vesicle glandular cells Low Enhanced P23634 +ENSG00000058668 ATP2B4 testis cells in seminiferous ducts High Enhanced P23634 +ENSG00000058668 ATP2B4 testis Leydig cells Medium Enhanced P23634 +ENSG00000059728 MXD1 epididymis glandular cells Medium Enhanced Q05195 +ENSG00000059728 MXD1 prostate glandular cells Low Enhanced Q05195 +ENSG00000059728 MXD1 seminal vesicle glandular cells Medium Enhanced Q05195 +ENSG00000059728 MXD1 testis cells in seminiferous ducts High Enhanced Q05195 +ENSG00000059728 MXD1 testis Leydig cells Medium Enhanced Q05195 +ENSG00000060069 CTDP1 epididymis glandular cells Low Supported Q9Y5B0 +ENSG00000060069 CTDP1 prostate glandular cells Low Supported Q9Y5B0 +ENSG00000060069 CTDP1 seminal vesicle glandular cells Medium Supported Q9Y5B0 +ENSG00000060069 CTDP1 testis cells in seminiferous ducts Low Supported Q9Y5B0 +ENSG00000060069 CTDP1 testis Leydig cells Low Supported Q9Y5B0 +ENSG00000060237 WNK1 epididymis glandular cells Low Enhanced Q9H4A3 +ENSG00000060237 WNK1 prostate glandular cells Low Enhanced Q9H4A3 +ENSG00000060237 WNK1 seminal vesicle glandular cells Low Enhanced Q9H4A3 +ENSG00000060237 WNK1 testis cells in seminiferous ducts High Enhanced Q9H4A3 +ENSG00000060237 WNK1 testis Leydig cells Medium Enhanced Q9H4A3 +ENSG00000060339 CCAR1 epididymis glandular cells High Supported Q8IX12 +ENSG00000060339 CCAR1 prostate glandular cells High Supported Q8IX12 +ENSG00000060339 CCAR1 seminal vesicle glandular cells High Supported Q8IX12 +ENSG00000060339 CCAR1 testis cells in seminiferous ducts High Supported Q8IX12 +ENSG00000060339 CCAR1 testis Leydig cells High Supported Q8IX12 +ENSG00000060491 OGFR epididymis glandular cells Low Enhanced Q9NZT2 +ENSG00000060491 OGFR prostate glandular cells Medium Enhanced Q9NZT2 +ENSG00000060491 OGFR seminal vesicle glandular cells Medium Enhanced Q9NZT2 +ENSG00000060491 OGFR testis cells in seminiferous ducts Low Enhanced Q9NZT2 +ENSG00000060491 OGFR testis Leydig cells Medium Enhanced Q9NZT2 +ENSG00000060688 SNRNP40 epididymis glandular cells High Supported Q96DI7 +ENSG00000060688 SNRNP40 prostate glandular cells Medium Supported Q96DI7 +ENSG00000060688 SNRNP40 seminal vesicle glandular cells High Supported Q96DI7 +ENSG00000060688 SNRNP40 testis cells in seminiferous ducts High Supported Q96DI7 +ENSG00000060688 SNRNP40 testis Leydig cells High Supported Q96DI7 +ENSG00000060762 MPC1 epididymis glandular cells Medium Enhanced Q9Y5U8 +ENSG00000060762 MPC1 prostate glandular cells High Enhanced Q9Y5U8 +ENSG00000060762 MPC1 seminal vesicle glandular cells High Enhanced Q9Y5U8 +ENSG00000060762 MPC1 testis cells in seminiferous ducts Medium Enhanced Q9Y5U8 +ENSG00000060762 MPC1 testis Leydig cells High Enhanced Q9Y5U8 +ENSG00000060971 ACAA1 epididymis glandular cells Low Enhanced P09110 +ENSG00000060971 ACAA1 seminal vesicle glandular cells Low Enhanced P09110 +ENSG00000060971 ACAA1 testis cells in seminiferous ducts Low Enhanced P09110 +ENSG00000060971 ACAA1 testis Leydig cells Low Enhanced P09110 +ENSG00000061676 NCKAP1 epididymis glandular cells Low Enhanced Q9Y2A7 +ENSG00000061676 NCKAP1 prostate glandular cells Low Enhanced Q9Y2A7 +ENSG00000061676 NCKAP1 seminal vesicle glandular cells Low Enhanced Q9Y2A7 +ENSG00000061676 NCKAP1 testis cells in seminiferous ducts Medium Enhanced Q9Y2A7 +ENSG00000061676 NCKAP1 testis Leydig cells Medium Enhanced Q9Y2A7 +ENSG00000061794 MRPS35 epididymis glandular cells Medium Enhanced P82673 +ENSG00000061794 MRPS35 prostate glandular cells High Enhanced P82673 +ENSG00000061794 MRPS35 seminal vesicle glandular cells High Enhanced P82673 +ENSG00000061794 MRPS35 testis cells in seminiferous ducts High Enhanced P82673 +ENSG00000061794 MRPS35 testis Leydig cells High Enhanced P82673 +ENSG00000062038 CDH3 epididymis glandular cells Medium Enhanced P22223 +ENSG00000062038 CDH3 prostate glandular cells Low Enhanced P22223 +ENSG00000062038 CDH3 seminal vesicle glandular cells Low Enhanced P22223 +ENSG00000062485 CS epididymis glandular cells High Enhanced O75390 +ENSG00000062485 CS prostate glandular cells High Enhanced O75390 +ENSG00000062485 CS seminal vesicle glandular cells High Enhanced O75390 +ENSG00000062485 CS testis cells in seminiferous ducts High Enhanced O75390 +ENSG00000062485 CS testis Leydig cells High Enhanced O75390 +ENSG00000062650 WAPL epididymis glandular cells Medium Enhanced Q7Z5K2 +ENSG00000062650 WAPL prostate glandular cells Medium Enhanced Q7Z5K2 +ENSG00000062650 WAPL seminal vesicle glandular cells Medium Enhanced Q7Z5K2 +ENSG00000062650 WAPL testis cells in seminiferous ducts Medium Enhanced Q7Z5K2 +ENSG00000062650 WAPL testis Leydig cells Medium Enhanced Q7Z5K2 +ENSG00000062822 POLD1 epididymis glandular cells Medium Enhanced P28340 +ENSG00000062822 POLD1 prostate glandular cells Medium Enhanced P28340 +ENSG00000062822 POLD1 seminal vesicle glandular cells Medium Enhanced P28340 +ENSG00000062822 POLD1 testis cells in seminiferous ducts High Enhanced P28340 +ENSG00000062822 POLD1 testis Leydig cells High Enhanced P28340 +ENSG00000063015 SEZ6 prostate glandular cells Low Enhanced Q53EL9 +ENSG00000063015 SEZ6 testis cells in seminiferous ducts Low Enhanced Q53EL9 +ENSG00000063015 SEZ6 testis Leydig cells Low Enhanced Q53EL9 +ENSG00000063241 ISOC2 epididymis glandular cells High Enhanced Q96AB3 +ENSG00000063241 ISOC2 prostate glandular cells High Enhanced Q96AB3 +ENSG00000063241 ISOC2 seminal vesicle glandular cells High Enhanced Q96AB3 +ENSG00000063241 ISOC2 testis cells in seminiferous ducts High Enhanced Q96AB3 +ENSG00000063241 ISOC2 testis Leydig cells High Enhanced Q96AB3 +ENSG00000063244 U2AF2 epididymis glandular cells High Supported P26368 +ENSG00000063244 U2AF2 prostate glandular cells Medium Supported P26368 +ENSG00000063244 U2AF2 seminal vesicle glandular cells High Supported P26368 +ENSG00000063244 U2AF2 testis cells in seminiferous ducts High Supported P26368 +ENSG00000063244 U2AF2 testis Leydig cells High Supported P26368 +ENSG00000064199 SPA17 epididymis glandular cells Medium Enhanced Q15506 +ENSG00000064199 SPA17 testis elongated or late spermatids High Enhanced Q15506 +ENSG00000064199 SPA17 testis pachytene spermatocytes High Enhanced Q15506 +ENSG00000064199 SPA17 testis round or early spermatids High Enhanced Q15506 +ENSG00000064199 SPA17 testis spermatogonia Low Enhanced Q15506 +ENSG00000064300 NGFR prostate glandular cells Medium Enhanced P08138 +ENSG00000064300 NGFR seminal vesicle glandular cells Medium Enhanced P08138 +ENSG00000064393 HIPK2 epididymis glandular cells High Supported Q9H2X6 +ENSG00000064393 HIPK2 prostate glandular cells Medium Supported Q9H2X6 +ENSG00000064393 HIPK2 seminal vesicle glandular cells Medium Supported Q9H2X6 +ENSG00000064393 HIPK2 testis cells in seminiferous ducts Medium Supported Q9H2X6 +ENSG00000064393 HIPK2 testis Leydig cells Medium Supported Q9H2X6 +ENSG00000064601 CTSA epididymis glandular cells High Enhanced P10619 +ENSG00000064601 CTSA prostate glandular cells Medium Enhanced P10619 +ENSG00000064601 CTSA seminal vesicle glandular cells High Enhanced P10619 +ENSG00000064601 CTSA testis cells in seminiferous ducts Medium Enhanced P10619 +ENSG00000064601 CTSA testis Leydig cells High Enhanced P10619 +ENSG00000064607 SUGP2 epididymis glandular cells Medium Enhanced Q8IX01 +ENSG00000064607 SUGP2 prostate glandular cells Medium Enhanced Q8IX01 +ENSG00000064607 SUGP2 seminal vesicle glandular cells Low Enhanced Q8IX01 +ENSG00000064607 SUGP2 testis cells in seminiferous ducts High Enhanced Q8IX01 +ENSG00000064607 SUGP2 testis Leydig cells Low Enhanced Q8IX01 +ENSG00000064687 ABCA7 epididymis glandular cells Low Enhanced Q8IZY2 +ENSG00000064687 ABCA7 prostate glandular cells Low Enhanced Q8IZY2 +ENSG00000064687 ABCA7 testis cells in seminiferous ducts Low Enhanced Q8IZY2 +ENSG00000064687 ABCA7 testis Leydig cells Low Enhanced Q8IZY2 +ENSG00000064703 DDX20 epididymis glandular cells Low Enhanced Q9UHI6 +ENSG00000064703 DDX20 testis cells in seminiferous ducts High Enhanced Q9UHI6 +ENSG00000064726 BTBD1 epididymis glandular cells Low Enhanced Q9H0C5 +ENSG00000064726 BTBD1 prostate glandular cells Medium Enhanced Q9H0C5 +ENSG00000064726 BTBD1 seminal vesicle glandular cells Medium Enhanced Q9H0C5 +ENSG00000064726 BTBD1 testis cells in seminiferous ducts Low Enhanced Q9H0C5 +ENSG00000064726 BTBD1 testis Leydig cells Low Enhanced Q9H0C5 +ENSG00000064787 BCAS1 prostate glandular cells High Enhanced O75363 +ENSG00000065054 SLC9A3R2 epididymis glandular cells Low Enhanced Q15599 +ENSG00000065057 NTHL1 epididymis glandular cells Medium Supported P78549 +ENSG00000065057 NTHL1 prostate glandular cells High Supported P78549 +ENSG00000065057 NTHL1 seminal vesicle glandular cells Medium Supported P78549 +ENSG00000065057 NTHL1 testis cells in seminiferous ducts Medium Supported P78549 +ENSG00000065057 NTHL1 testis Leydig cells Medium Supported P78549 +ENSG00000065154 OAT seminal vesicle glandular cells Medium Enhanced P04181 +ENSG00000065154 OAT testis cells in seminiferous ducts Low Enhanced P04181 +ENSG00000065154 OAT testis Leydig cells Medium Enhanced P04181 +ENSG00000065371 ROPN1 epididymis glandular cells Low Supported Q9HAT0 +ENSG00000065371 ROPN1 testis cells in seminiferous ducts Medium Supported Q9HAT0 +ENSG00000065427 KARS epididymis glandular cells High Enhanced Q15046 +ENSG00000065427 KARS prostate glandular cells High Enhanced Q15046 +ENSG00000065427 KARS seminal vesicle glandular cells High Enhanced Q15046 +ENSG00000065427 KARS testis cells in seminiferous ducts High Enhanced Q15046 +ENSG00000065427 KARS testis Leydig cells Medium Enhanced Q15046 +ENSG00000065485 PDIA5 epididymis glandular cells High Enhanced Q14554 +ENSG00000065485 PDIA5 prostate glandular cells Medium Enhanced Q14554 +ENSG00000065485 PDIA5 seminal vesicle glandular cells Low Enhanced Q14554 +ENSG00000065485 PDIA5 testis cells in seminiferous ducts High Enhanced Q14554 +ENSG00000065485 PDIA5 testis Leydig cells Medium Enhanced Q14554 +ENSG00000065518 NDUFB4 epididymis glandular cells Low Enhanced O95168 +ENSG00000065518 NDUFB4 prostate glandular cells High Enhanced O95168 +ENSG00000065518 NDUFB4 seminal vesicle glandular cells High Enhanced O95168 +ENSG00000065518 NDUFB4 testis cells in seminiferous ducts Low Enhanced O95168 +ENSG00000065518 NDUFB4 testis Leydig cells Medium Enhanced O95168 +ENSG00000065526 SPEN epididymis glandular cells High Supported Q96T58 +ENSG00000065526 SPEN prostate glandular cells High Supported Q96T58 +ENSG00000065526 SPEN seminal vesicle glandular cells Medium Supported Q96T58 +ENSG00000065526 SPEN testis cells in seminiferous ducts High Supported Q96T58 +ENSG00000065526 SPEN testis Leydig cells High Supported Q96T58 +ENSG00000065548 ZC3H15 epididymis glandular cells Medium Enhanced Q8WU90 +ENSG00000065548 ZC3H15 prostate glandular cells Medium Enhanced Q8WU90 +ENSG00000065548 ZC3H15 seminal vesicle glandular cells High Enhanced Q8WU90 +ENSG00000065548 ZC3H15 testis cells in seminiferous ducts Medium Enhanced Q8WU90 +ENSG00000065548 ZC3H15 testis Leydig cells Medium Enhanced Q8WU90 +ENSG00000065559 MAP2K4 epididymis glandular cells Low Enhanced P45985 +ENSG00000065559 MAP2K4 prostate glandular cells Low Enhanced P45985 +ENSG00000065559 MAP2K4 seminal vesicle glandular cells Low Enhanced P45985 +ENSG00000065559 MAP2K4 testis cells in seminiferous ducts Low Enhanced P45985 +ENSG00000065559 MAP2K4 testis Leydig cells Low Enhanced P45985 +ENSG00000065833 ME1 epididymis glandular cells Low Enhanced P48163 +ENSG00000065833 ME1 testis cells in seminiferous ducts Medium Enhanced P48163 +ENSG00000065833 ME1 testis Leydig cells Medium Enhanced P48163 +ENSG00000065978 YBX1 epididymis glandular cells Medium Supported P67809 +ENSG00000065978 YBX1 prostate glandular cells Medium Supported P67809 +ENSG00000065978 YBX1 seminal vesicle glandular cells Low Supported P67809 +ENSG00000065978 YBX1 testis cells in seminiferous ducts High Supported P67809 +ENSG00000065978 YBX1 testis Leydig cells Low Supported P67809 +ENSG00000066032 CTNNA2 testis cells in seminiferous ducts Low Enhanced P26232 +ENSG00000066032 CTNNA2 testis Leydig cells Low Enhanced P26232 +ENSG00000066084 DIP2B epididymis glandular cells Medium Enhanced Q9P265 +ENSG00000066084 DIP2B prostate glandular cells Medium Enhanced Q9P265 +ENSG00000066084 DIP2B testis cells in seminiferous ducts Medium Enhanced Q9P265 +ENSG00000066084 DIP2B testis Leydig cells High Enhanced Q9P265 +ENSG00000066117 SMARCD1 epididymis glandular cells Medium Supported Q96GM5 +ENSG00000066117 SMARCD1 prostate glandular cells Medium Supported Q96GM5 +ENSG00000066117 SMARCD1 seminal vesicle glandular cells High Supported Q96GM5 +ENSG00000066117 SMARCD1 testis cells in seminiferous ducts High Supported Q96GM5 +ENSG00000066117 SMARCD1 testis Leydig cells Medium Supported Q96GM5 +ENSG00000066336 SPI1 epididymis glandular cells Low Enhanced P17947 +ENSG00000066379 ZNRD1 epididymis glandular cells High Supported NA +ENSG00000066379 ZNRD1 prostate glandular cells Medium Supported NA +ENSG00000066379 ZNRD1 seminal vesicle glandular cells High Supported NA +ENSG00000066379 ZNRD1 testis cells in seminiferous ducts High Supported NA +ENSG00000066379 ZNRD1 testis Leydig cells High Supported NA +ENSG00000066455 GOLGA5 epididymis glandular cells High Enhanced Q8TBA6 +ENSG00000066455 GOLGA5 prostate glandular cells High Enhanced Q8TBA6 +ENSG00000066455 GOLGA5 seminal vesicle glandular cells High Enhanced Q8TBA6 +ENSG00000066455 GOLGA5 testis cells in seminiferous ducts High Enhanced Q8TBA6 +ENSG00000066455 GOLGA5 testis Leydig cells High Enhanced Q8TBA6 +ENSG00000066777 ARFGEF1 epididymis glandular cells Medium Supported Q9Y6D6 +ENSG00000066777 ARFGEF1 prostate glandular cells Medium Supported Q9Y6D6 +ENSG00000066777 ARFGEF1 seminal vesicle glandular cells Medium Supported Q9Y6D6 +ENSG00000066777 ARFGEF1 testis cells in seminiferous ducts Medium Supported Q9Y6D6 +ENSG00000066777 ARFGEF1 testis Leydig cells Medium Supported Q9Y6D6 +ENSG00000066827 ZFAT testis cells in seminiferous ducts Low Enhanced Q9P243 +ENSG00000066923 STAG3 testis cells in seminiferous ducts High Enhanced Q9UJ98 +ENSG00000067066 SP100 epididymis glandular cells Medium Enhanced P23497 +ENSG00000067066 SP100 prostate glandular cells Low Enhanced P23497 +ENSG00000067066 SP100 seminal vesicle glandular cells Medium Enhanced P23497 +ENSG00000067066 SP100 testis cells in seminiferous ducts Low Enhanced P23497 +ENSG00000067066 SP100 testis Leydig cells Medium Enhanced P23497 +ENSG00000067082 KLF6 epididymis glandular cells Medium Supported Q99612 +ENSG00000067082 KLF6 prostate glandular cells Low Supported Q99612 +ENSG00000067082 KLF6 seminal vesicle glandular cells Low Supported Q99612 +ENSG00000067082 KLF6 testis cells in seminiferous ducts Medium Supported Q99612 +ENSG00000067082 KLF6 testis Leydig cells Low Supported Q99612 +ENSG00000067113 PLPP1 epididymis glandular cells Medium Enhanced O14494 +ENSG00000067113 PLPP1 prostate glandular cells High Enhanced O14494 +ENSG00000067334 DNTTIP2 epididymis glandular cells Medium Enhanced Q5QJE6 +ENSG00000067334 DNTTIP2 testis cells in seminiferous ducts Medium Enhanced Q5QJE6 +ENSG00000067334 DNTTIP2 testis Leydig cells Medium Enhanced Q5QJE6 +ENSG00000067369 TP53BP1 epididymis glandular cells Medium Supported Q12888 +ENSG00000067369 TP53BP1 prostate glandular cells High Supported Q12888 +ENSG00000067369 TP53BP1 seminal vesicle glandular cells Medium Supported Q12888 +ENSG00000067369 TP53BP1 testis cells in seminiferous ducts High Supported Q12888 +ENSG00000067369 TP53BP1 testis Leydig cells Medium Supported Q12888 +ENSG00000067606 PRKCZ epididymis glandular cells Medium Enhanced Q05513 +ENSG00000067606 PRKCZ prostate glandular cells Medium Enhanced Q05513 +ENSG00000067606 PRKCZ testis cells in seminiferous ducts Low Enhanced Q05513 +ENSG00000067704 IARS2 epididymis glandular cells Medium Enhanced Q9NSE4 +ENSG00000067704 IARS2 prostate glandular cells Medium Enhanced Q9NSE4 +ENSG00000067704 IARS2 seminal vesicle glandular cells High Enhanced Q9NSE4 +ENSG00000067704 IARS2 testis cells in seminiferous ducts Medium Enhanced Q9NSE4 +ENSG00000067704 IARS2 testis Leydig cells High Enhanced Q9NSE4 +ENSG00000067829 IDH3G epididymis glandular cells High Enhanced P51553 +ENSG00000067829 IDH3G prostate glandular cells Medium Enhanced P51553 +ENSG00000067829 IDH3G seminal vesicle glandular cells Medium Enhanced P51553 +ENSG00000067829 IDH3G testis cells in seminiferous ducts Medium Enhanced P51553 +ENSG00000067829 IDH3G testis Leydig cells Medium Enhanced P51553 +ENSG00000068078 FGFR3 testis cells in seminiferous ducts Medium Enhanced P22607 +ENSG00000068366 ACSL4 epididymis glandular cells Low Enhanced O60488 +ENSG00000068366 ACSL4 prostate glandular cells Low Enhanced O60488 +ENSG00000068366 ACSL4 seminal vesicle glandular cells Low Enhanced O60488 +ENSG00000068366 ACSL4 testis cells in seminiferous ducts Medium Enhanced O60488 +ENSG00000068366 ACSL4 testis Leydig cells Medium Enhanced O60488 +ENSG00000068383 INPP5A epididymis glandular cells High Enhanced Q14642 +ENSG00000068383 INPP5A prostate glandular cells Medium Enhanced Q14642 +ENSG00000068383 INPP5A seminal vesicle glandular cells High Enhanced Q14642 +ENSG00000068383 INPP5A testis cells in seminiferous ducts Medium Enhanced Q14642 +ENSG00000068383 INPP5A testis Leydig cells High Enhanced Q14642 +ENSG00000068394 GPKOW epididymis glandular cells High Enhanced Q92917 +ENSG00000068394 GPKOW prostate glandular cells High Enhanced Q92917 +ENSG00000068394 GPKOW seminal vesicle glandular cells High Enhanced Q92917 +ENSG00000068394 GPKOW testis cells in seminiferous ducts High Enhanced Q92917 +ENSG00000068394 GPKOW testis Leydig cells High Enhanced Q92917 +ENSG00000068400 GRIPAP1 epididymis glandular cells Medium Enhanced Q4V328 +ENSG00000068400 GRIPAP1 prostate glandular cells Medium Enhanced Q4V328 +ENSG00000068400 GRIPAP1 seminal vesicle glandular cells High Enhanced Q4V328 +ENSG00000068400 GRIPAP1 testis cells in seminiferous ducts High Enhanced Q4V328 +ENSG00000068400 GRIPAP1 testis Leydig cells Medium Enhanced Q4V328 +ENSG00000068615 REEP1 testis elongated or late spermatids Medium Enhanced Q9H902 +ENSG00000068615 REEP1 testis pachytene spermatocytes Medium Enhanced Q9H902 +ENSG00000068615 REEP1 testis preleptotene spermatocytes Medium Enhanced Q9H902 +ENSG00000068615 REEP1 testis round or early spermatids Medium Enhanced Q9H902 +ENSG00000068615 REEP1 testis sertoli cells High Enhanced Q9H902 +ENSG00000068615 REEP1 testis spermatogonia Medium Enhanced Q9H902 +ENSG00000068654 POLR1A epididymis glandular cells Medium Supported O95602 +ENSG00000068654 POLR1A prostate glandular cells Medium Supported O95602 +ENSG00000068654 POLR1A seminal vesicle glandular cells Low Supported O95602 +ENSG00000068654 POLR1A testis cells in seminiferous ducts High Supported O95602 +ENSG00000068654 POLR1A testis Leydig cells Medium Supported O95602 +ENSG00000068724 TTC7A epididymis glandular cells Medium Enhanced Q9ULT0 +ENSG00000068724 TTC7A prostate glandular cells Medium Enhanced Q9ULT0 +ENSG00000068724 TTC7A seminal vesicle glandular cells High Enhanced Q9ULT0 +ENSG00000068724 TTC7A testis cells in seminiferous ducts Medium Enhanced Q9ULT0 +ENSG00000068724 TTC7A testis Leydig cells Medium Enhanced Q9ULT0 +ENSG00000068912 ERLEC1 epididymis glandular cells Medium Enhanced Q96DZ1 +ENSG00000068912 ERLEC1 prostate glandular cells Low Enhanced Q96DZ1 +ENSG00000068912 ERLEC1 seminal vesicle glandular cells Medium Enhanced Q96DZ1 +ENSG00000068912 ERLEC1 testis cells in seminiferous ducts High Enhanced Q96DZ1 +ENSG00000068912 ERLEC1 testis Leydig cells Medium Enhanced Q96DZ1 +ENSG00000068985 PAGE1 testis elongated or late spermatids Low Enhanced O75459 +ENSG00000068985 PAGE1 testis pachytene spermatocytes Medium Enhanced O75459 +ENSG00000068985 PAGE1 testis preleptotene spermatocytes High Enhanced O75459 +ENSG00000068985 PAGE1 testis round or early spermatids Medium Enhanced O75459 +ENSG00000068985 PAGE1 testis spermatogonia High Enhanced O75459 +ENSG00000069206 ADAM7 epididymis glandular cells High Enhanced Q9H2U9 +ENSG00000069275 NUCKS1 epididymis glandular cells High Supported Q9H1E3 +ENSG00000069275 NUCKS1 prostate glandular cells High Supported Q9H1E3 +ENSG00000069275 NUCKS1 seminal vesicle glandular cells High Supported Q9H1E3 +ENSG00000069275 NUCKS1 testis cells in seminiferous ducts Medium Supported Q9H1E3 +ENSG00000069275 NUCKS1 testis Leydig cells High Supported Q9H1E3 +ENSG00000069329 VPS35 epididymis glandular cells Medium Enhanced Q96QK1 +ENSG00000069329 VPS35 prostate glandular cells Medium Enhanced Q96QK1 +ENSG00000069329 VPS35 seminal vesicle glandular cells Medium Enhanced Q96QK1 +ENSG00000069329 VPS35 testis cells in seminiferous ducts High Enhanced Q96QK1 +ENSG00000069329 VPS35 testis Leydig cells High Enhanced Q96QK1 +ENSG00000069424 KCNAB2 epididymis glandular cells Low Enhanced Q13303 +ENSG00000069424 KCNAB2 prostate glandular cells Low Enhanced Q13303 +ENSG00000069424 KCNAB2 seminal vesicle glandular cells Low Enhanced Q13303 +ENSG00000069424 KCNAB2 testis cells in seminiferous ducts Low Enhanced Q13303 +ENSG00000069535 MAOB epididymis glandular cells High Enhanced P27338 +ENSG00000069535 MAOB prostate glandular cells High Enhanced P27338 +ENSG00000069535 MAOB testis cells in seminiferous ducts Low Enhanced P27338 +ENSG00000069535 MAOB testis Leydig cells High Enhanced P27338 +ENSG00000069702 TGFBR3 epididymis glandular cells Low Supported Q03167 +ENSG00000069702 TGFBR3 seminal vesicle glandular cells Low Supported Q03167 +ENSG00000069702 TGFBR3 testis cells in seminiferous ducts Low Supported Q03167 +ENSG00000069702 TGFBR3 testis Leydig cells Medium Supported Q03167 +ENSG00000069849 ATP1B3 epididymis glandular cells Low Enhanced P54709 +ENSG00000069849 ATP1B3 prostate glandular cells Medium Enhanced P54709 +ENSG00000069849 ATP1B3 seminal vesicle glandular cells Low Enhanced P54709 +ENSG00000069849 ATP1B3 testis cells in seminiferous ducts Low Enhanced P54709 +ENSG00000069849 ATP1B3 testis Leydig cells Medium Enhanced P54709 +ENSG00000069974 RAB27A epididymis glandular cells Low Enhanced P51159 +ENSG00000069974 RAB27A prostate glandular cells High Enhanced P51159 +ENSG00000069974 RAB27A seminal vesicle glandular cells Low Enhanced P51159 +ENSG00000069974 RAB27A testis Leydig cells Low Enhanced P51159 +ENSG00000070018 LRP6 epididymis glandular cells Medium Enhanced NA +ENSG00000070018 LRP6 prostate glandular cells Medium Enhanced NA +ENSG00000070018 LRP6 seminal vesicle glandular cells Medium Enhanced NA +ENSG00000070018 LRP6 testis cells in seminiferous ducts Medium Enhanced NA +ENSG00000070018 LRP6 testis Leydig cells Medium Enhanced NA +ENSG00000070087 PFN2 epididymis glandular cells High Enhanced P35080 +ENSG00000070087 PFN2 prostate glandular cells Medium Enhanced P35080 +ENSG00000070087 PFN2 seminal vesicle glandular cells Medium Enhanced P35080 +ENSG00000070087 PFN2 testis cells in seminiferous ducts Low Enhanced P35080 +ENSG00000070087 PFN2 testis Leydig cells Low Enhanced P35080 +ENSG00000070182 SPTB epididymis glandular cells High Enhanced P11277 +ENSG00000070495 JMJD6 epididymis glandular cells Medium Supported Q6NYC1 +ENSG00000070495 JMJD6 prostate glandular cells Medium Supported Q6NYC1 +ENSG00000070495 JMJD6 seminal vesicle glandular cells Medium Supported Q6NYC1 +ENSG00000070495 JMJD6 testis cells in seminiferous ducts High Supported Q6NYC1 +ENSG00000070495 JMJD6 testis Leydig cells High Supported Q6NYC1 +ENSG00000070501 POLB epididymis glandular cells Medium Enhanced P06746 +ENSG00000070501 POLB prostate glandular cells Medium Enhanced P06746 +ENSG00000070501 POLB seminal vesicle glandular cells Medium Enhanced P06746 +ENSG00000070501 POLB testis cells in seminiferous ducts High Enhanced P06746 +ENSG00000070501 POLB testis Leydig cells Low Enhanced P06746 +ENSG00000070540 WIPI1 epididymis glandular cells Low Enhanced Q5MNZ9 +ENSG00000070540 WIPI1 prostate glandular cells Medium Enhanced Q5MNZ9 +ENSG00000070540 WIPI1 seminal vesicle glandular cells Medium Enhanced Q5MNZ9 +ENSG00000070540 WIPI1 testis cells in seminiferous ducts Low Enhanced Q5MNZ9 +ENSG00000070540 WIPI1 testis Leydig cells Medium Enhanced Q5MNZ9 +ENSG00000070756 PABPC1 epididymis glandular cells Medium Enhanced P11940 +ENSG00000070756 PABPC1 prostate glandular cells Medium Enhanced P11940 +ENSG00000070756 PABPC1 seminal vesicle glandular cells Medium Enhanced P11940 +ENSG00000070756 PABPC1 testis cells in seminiferous ducts High Enhanced P11940 +ENSG00000070756 PABPC1 testis Leydig cells Low Enhanced P11940 +ENSG00000070785 EIF2B3 epididymis glandular cells High Supported Q9NR50 +ENSG00000070785 EIF2B3 prostate glandular cells Medium Supported Q9NR50 +ENSG00000070785 EIF2B3 seminal vesicle glandular cells Medium Supported Q9NR50 +ENSG00000070785 EIF2B3 testis cells in seminiferous ducts Medium Supported Q9NR50 +ENSG00000070785 EIF2B3 testis Leydig cells Medium Supported Q9NR50 +ENSG00000070808 CAMK2A epididymis glandular cells Medium Enhanced Q9UQM7 +ENSG00000070808 CAMK2A prostate glandular cells Low Enhanced Q9UQM7 +ENSG00000070808 CAMK2A testis cells in seminiferous ducts Medium Enhanced Q9UQM7 +ENSG00000070808 CAMK2A testis Leydig cells High Enhanced Q9UQM7 +ENSG00000070814 TCOF1 epididymis glandular cells Medium Enhanced Q13428 +ENSG00000070814 TCOF1 prostate glandular cells Low Enhanced Q13428 +ENSG00000070814 TCOF1 seminal vesicle glandular cells Low Enhanced Q13428 +ENSG00000070814 TCOF1 testis cells in seminiferous ducts Medium Enhanced Q13428 +ENSG00000070814 TCOF1 testis Leydig cells Medium Enhanced Q13428 +ENSG00000070882 OSBPL3 testis Leydig cells Low Enhanced Q9H4L5 +ENSG00000070950 RAD18 epididymis glandular cells Low Supported Q9NS91 +ENSG00000070950 RAD18 prostate glandular cells Low Supported Q9NS91 +ENSG00000070950 RAD18 seminal vesicle glandular cells Medium Supported Q9NS91 +ENSG00000070950 RAD18 testis cells in seminiferous ducts Medium Supported Q9NS91 +ENSG00000070950 RAD18 testis Leydig cells Medium Supported Q9NS91 +ENSG00000070961 ATP2B1 epididymis glandular cells Medium Enhanced P20020 +ENSG00000070961 ATP2B1 prostate glandular cells Medium Enhanced P20020 +ENSG00000070961 ATP2B1 testis cells in seminiferous ducts Medium Enhanced P20020 +ENSG00000070961 ATP2B1 testis Leydig cells Medium Enhanced P20020 +ENSG00000071073 MGAT4A epididymis glandular cells Low Enhanced Q9UM21 +ENSG00000071073 MGAT4A prostate glandular cells Low Enhanced Q9UM21 +ENSG00000071073 MGAT4A seminal vesicle glandular cells Medium Enhanced Q9UM21 +ENSG00000071073 MGAT4A testis cells in seminiferous ducts Low Enhanced Q9UM21 +ENSG00000071073 MGAT4A testis Leydig cells Medium Enhanced Q9UM21 +ENSG00000071282 LMCD1 prostate glandular cells Low Enhanced Q9NZU5 +ENSG00000071282 LMCD1 seminal vesicle glandular cells Medium Enhanced Q9NZU5 +ENSG00000071282 LMCD1 testis cells in seminiferous ducts Medium Enhanced Q9NZU5 +ENSG00000071282 LMCD1 testis Leydig cells Low Enhanced Q9NZU5 +ENSG00000071539 TRIP13 testis elongated or late spermatids High Enhanced Q15645 +ENSG00000071539 TRIP13 testis Leydig cells Low Enhanced Q15645 +ENSG00000071539 TRIP13 testis pachytene spermatocytes Medium Enhanced Q15645 +ENSG00000071539 TRIP13 testis preleptotene spermatocytes Low Enhanced Q15645 +ENSG00000071539 TRIP13 testis round or early spermatids Medium Enhanced Q15645 +ENSG00000071539 TRIP13 testis spermatogonia Low Enhanced Q15645 +ENSG00000071626 DAZAP1 epididymis glandular cells Medium Enhanced Q96EP5 +ENSG00000071626 DAZAP1 prostate glandular cells Medium Enhanced Q96EP5 +ENSG00000071626 DAZAP1 seminal vesicle glandular cells Medium Enhanced Q96EP5 +ENSG00000071626 DAZAP1 testis cells in seminiferous ducts High Enhanced Q96EP5 +ENSG00000071626 DAZAP1 testis Leydig cells Medium Enhanced Q96EP5 +ENSG00000071655 MBD3 epididymis glandular cells Medium Supported O95983 +ENSG00000071655 MBD3 testis cells in seminiferous ducts Medium Supported O95983 +ENSG00000071655 MBD3 testis Leydig cells Low Supported O95983 +ENSG00000071859 FAM50A epididymis glandular cells High Supported Q14320 +ENSG00000071859 FAM50A prostate glandular cells High Supported Q14320 +ENSG00000071859 FAM50A testis cells in seminiferous ducts Medium Supported Q14320 +ENSG00000071859 FAM50A testis Leydig cells Medium Supported Q14320 +ENSG00000072042 RDH11 prostate glandular cells Medium Enhanced Q8TC12 +ENSG00000072042 RDH11 testis cells in seminiferous ducts Low Enhanced Q8TC12 +ENSG00000072195 SPEG epididymis glandular cells Medium Enhanced Q15772 +ENSG00000072195 SPEG seminal vesicle glandular cells Medium Enhanced Q15772 +ENSG00000072195 SPEG testis Leydig cells Medium Enhanced Q15772 +ENSG00000072274 TFRC epididymis glandular cells Low Enhanced P02786 +ENSG00000072274 TFRC prostate glandular cells Low Enhanced P02786 +ENSG00000072274 TFRC testis cells in seminiferous ducts Medium Enhanced P02786 +ENSG00000072274 TFRC testis Leydig cells Low Enhanced P02786 +ENSG00000072415 MPP5 epididymis glandular cells Medium Enhanced Q8N3R9 +ENSG00000072501 SMC1A epididymis glandular cells Medium Supported Q14683 +ENSG00000072501 SMC1A prostate glandular cells Medium Supported Q14683 +ENSG00000072501 SMC1A seminal vesicle glandular cells Medium Supported Q14683 +ENSG00000072501 SMC1A testis cells in seminiferous ducts Medium Supported Q14683 +ENSG00000072501 SMC1A testis Leydig cells Medium Supported Q14683 +ENSG00000072571 HMMR testis Leydig cells Low Enhanced O75330 +ENSG00000072571 HMMR testis pachytene spermatocytes High Enhanced O75330 +ENSG00000072682 P4HA2 epididymis glandular cells Medium Enhanced O15460 +ENSG00000072682 P4HA2 seminal vesicle glandular cells Low Enhanced O15460 +ENSG00000072682 P4HA2 testis cells in seminiferous ducts Medium Enhanced O15460 +ENSG00000072694 FCGR2B epididymis glandular cells Low Enhanced P31994 +ENSG00000072694 FCGR2B testis cells in seminiferous ducts Low Enhanced P31994 +ENSG00000072778 ACADVL epididymis glandular cells Low Enhanced P49748 +ENSG00000072778 ACADVL prostate glandular cells Medium Enhanced P49748 +ENSG00000072778 ACADVL seminal vesicle glandular cells Medium Enhanced P49748 +ENSG00000072778 ACADVL testis cells in seminiferous ducts Low Enhanced P49748 +ENSG00000072778 ACADVL testis Leydig cells Medium Enhanced P49748 +ENSG00000072786 STK10 epididymis glandular cells Low Enhanced O94804 +ENSG00000072786 STK10 seminal vesicle glandular cells Low Enhanced O94804 +ENSG00000072786 STK10 testis cells in seminiferous ducts Medium Enhanced O94804 +ENSG00000072849 DERL2 epididymis glandular cells High Enhanced Q9GZP9 +ENSG00000072849 DERL2 prostate glandular cells Medium Enhanced Q9GZP9 +ENSG00000072849 DERL2 seminal vesicle glandular cells Medium Enhanced Q9GZP9 +ENSG00000072849 DERL2 testis cells in seminiferous ducts Medium Enhanced Q9GZP9 +ENSG00000072849 DERL2 testis Leydig cells Medium Enhanced Q9GZP9 +ENSG00000072858 SIDT1 epididymis glandular cells Low Enhanced Q9NXL6 +ENSG00000072858 SIDT1 prostate glandular cells Medium Enhanced Q9NXL6 +ENSG00000072858 SIDT1 seminal vesicle glandular cells Medium Enhanced Q9NXL6 +ENSG00000072858 SIDT1 testis cells in seminiferous ducts Medium Enhanced Q9NXL6 +ENSG00000072858 SIDT1 testis Leydig cells Medium Enhanced Q9NXL6 +ENSG00000073050 XRCC1 epididymis glandular cells High Supported P18887 +ENSG00000073050 XRCC1 prostate glandular cells Medium Supported P18887 +ENSG00000073050 XRCC1 seminal vesicle glandular cells Medium Supported P18887 +ENSG00000073050 XRCC1 testis cells in seminiferous ducts High Supported P18887 +ENSG00000073050 XRCC1 testis Leydig cells Medium Supported P18887 +ENSG00000073060 SCARB1 testis Leydig cells High Enhanced Q8WTV0 +ENSG00000073111 MCM2 epididymis glandular cells Low Enhanced P49736 +ENSG00000073111 MCM2 prostate glandular cells Low Enhanced P49736 +ENSG00000073111 MCM2 testis cells in seminiferous ducts Medium Enhanced P49736 +ENSG00000073150 PANX2 epididymis glandular cells Low Enhanced Q96RD6 +ENSG00000073150 PANX2 testis cells in seminiferous ducts Low Enhanced Q96RD6 +ENSG00000073150 PANX2 testis Leydig cells Low Enhanced Q96RD6 +ENSG00000073282 TP63 epididymis glandular cells High Enhanced Q9H3D4 +ENSG00000073282 TP63 prostate glandular cells Medium Enhanced Q9H3D4 +ENSG00000073282 TP63 seminal vesicle glandular cells Medium Enhanced Q9H3D4 +ENSG00000073464 CLCN4 testis cells in seminiferous ducts Low Enhanced P51793 +ENSG00000073578 SDHA epididymis glandular cells Low Enhanced P31040 +ENSG00000073578 SDHA prostate glandular cells Medium Enhanced P31040 +ENSG00000073578 SDHA seminal vesicle glandular cells Medium Enhanced P31040 +ENSG00000073578 SDHA testis cells in seminiferous ducts Medium Enhanced P31040 +ENSG00000073578 SDHA testis Leydig cells High Enhanced P31040 +ENSG00000073584 SMARCE1 epididymis glandular cells High Enhanced Q969G3 +ENSG00000073584 SMARCE1 prostate glandular cells High Enhanced Q969G3 +ENSG00000073584 SMARCE1 seminal vesicle glandular cells High Enhanced Q969G3 +ENSG00000073584 SMARCE1 testis cells in seminiferous ducts High Enhanced Q969G3 +ENSG00000073584 SMARCE1 testis Leydig cells High Enhanced Q969G3 +ENSG00000073598 FNDC8 testis elongated or late spermatids High Supported Q8TC99 +ENSG00000073598 FNDC8 testis Leydig cells Low Supported Q8TC99 +ENSG00000073598 FNDC8 testis pachytene spermatocytes Low Supported Q8TC99 +ENSG00000073598 FNDC8 testis preleptotene spermatocytes Low Supported Q8TC99 +ENSG00000073598 FNDC8 testis round or early spermatids Medium Supported Q8TC99 +ENSG00000073598 FNDC8 testis sertoli cells Low Supported Q8TC99 +ENSG00000073598 FNDC8 testis spermatogonia Low Supported Q8TC99 +ENSG00000073734 ABCB11 testis Leydig cells Low Enhanced O95342 +ENSG00000073792 IGF2BP2 epididymis glandular cells Medium Enhanced Q9Y6M1 +ENSG00000073792 IGF2BP2 prostate glandular cells Low Enhanced Q9Y6M1 +ENSG00000073792 IGF2BP2 seminal vesicle glandular cells Medium Enhanced Q9Y6M1 +ENSG00000073792 IGF2BP2 testis cells in seminiferous ducts Medium Enhanced Q9Y6M1 +ENSG00000073792 IGF2BP2 testis Leydig cells Medium Enhanced Q9Y6M1 +ENSG00000073849 ST6GAL1 prostate glandular cells High Supported P15907 +ENSG00000073921 PICALM epididymis glandular cells Medium Enhanced Q13492 +ENSG00000073921 PICALM prostate glandular cells Medium Enhanced Q13492 +ENSG00000073921 PICALM seminal vesicle glandular cells Medium Enhanced Q13492 +ENSG00000073921 PICALM testis cells in seminiferous ducts Medium Enhanced Q13492 +ENSG00000073921 PICALM testis Leydig cells High Enhanced Q13492 +ENSG00000073969 NSF epididymis glandular cells Low Enhanced NA +ENSG00000073969 NSF prostate glandular cells Low Enhanced NA +ENSG00000073969 NSF seminal vesicle glandular cells Low Enhanced NA +ENSG00000073969 NSF testis cells in seminiferous ducts Medium Enhanced NA +ENSG00000073969 NSF testis Leydig cells Low Enhanced NA +ENSG00000074071 MRPS34 epididymis glandular cells High Supported P82930 +ENSG00000074071 MRPS34 prostate glandular cells Medium Supported P82930 +ENSG00000074071 MRPS34 seminal vesicle glandular cells High Supported P82930 +ENSG00000074071 MRPS34 testis cells in seminiferous ducts Medium Supported P82930 +ENSG00000074071 MRPS34 testis Leydig cells High Supported P82930 +ENSG00000074266 EED epididymis glandular cells Low Supported O75530 +ENSG00000074266 EED seminal vesicle glandular cells Medium Supported O75530 +ENSG00000074266 EED testis cells in seminiferous ducts High Supported O75530 +ENSG00000074266 EED testis Leydig cells High Supported O75530 +ENSG00000074356 NCBP3 epididymis glandular cells High Supported Q53F19 +ENSG00000074356 NCBP3 prostate glandular cells High Supported Q53F19 +ENSG00000074356 NCBP3 seminal vesicle glandular cells Medium Supported Q53F19 +ENSG00000074356 NCBP3 testis cells in seminiferous ducts High Supported Q53F19 +ENSG00000074356 NCBP3 testis Leydig cells Medium Supported Q53F19 +ENSG00000074410 CA12 seminal vesicle glandular cells Low Enhanced O43570 +ENSG00000074416 MGLL epididymis glandular cells Medium Enhanced Q99685 +ENSG00000074416 MGLL prostate glandular cells Medium Enhanced Q99685 +ENSG00000074416 MGLL testis cells in seminiferous ducts Low Enhanced Q99685 +ENSG00000074416 MGLL testis Leydig cells Medium Enhanced Q99685 +ENSG00000074582 BCS1L epididymis glandular cells Medium Enhanced Q9Y276 +ENSG00000074582 BCS1L prostate glandular cells Medium Enhanced Q9Y276 +ENSG00000074582 BCS1L seminal vesicle glandular cells Medium Enhanced Q9Y276 +ENSG00000074582 BCS1L testis cells in seminiferous ducts Medium Enhanced Q9Y276 +ENSG00000074582 BCS1L testis Leydig cells High Enhanced Q9Y276 +ENSG00000074660 SCARF1 prostate glandular cells Low Enhanced NA +ENSG00000074660 SCARF1 seminal vesicle glandular cells Low Enhanced NA +ENSG00000074695 LMAN1 epididymis glandular cells High Supported P49257 +ENSG00000074695 LMAN1 prostate glandular cells Medium Supported P49257 +ENSG00000074695 LMAN1 seminal vesicle glandular cells High Supported P49257 +ENSG00000074695 LMAN1 testis cells in seminiferous ducts Medium Supported P49257 +ENSG00000074695 LMAN1 testis Leydig cells High Supported P49257 +ENSG00000074696 HACD3 epididymis glandular cells Medium Enhanced Q9P035 +ENSG00000074696 HACD3 prostate glandular cells Medium Enhanced Q9P035 +ENSG00000074696 HACD3 seminal vesicle glandular cells Medium Enhanced Q9P035 +ENSG00000074696 HACD3 testis cells in seminiferous ducts High Enhanced Q9P035 +ENSG00000074696 HACD3 testis Leydig cells High Enhanced Q9P035 +ENSG00000074800 ENO1 epididymis glandular cells Medium Enhanced P06733 +ENSG00000074800 ENO1 prostate glandular cells Medium Enhanced P06733 +ENSG00000074800 ENO1 seminal vesicle glandular cells Medium Enhanced P06733 +ENSG00000074800 ENO1 testis cells in seminiferous ducts Medium Enhanced P06733 +ENSG00000074800 ENO1 testis Leydig cells Medium Enhanced P06733 +ENSG00000075043 KCNQ2 testis cells in seminiferous ducts Low Enhanced O43526 +ENSG00000075131 TIPIN epididymis glandular cells Low Enhanced Q9BVW5 +ENSG00000075131 TIPIN testis preleptotene spermatocytes High Enhanced Q9BVW5 +ENSG00000075131 TIPIN testis spermatogonia Medium Enhanced Q9BVW5 +ENSG00000075142 SRI epididymis glandular cells Low Enhanced P30626 +ENSG00000075142 SRI testis Leydig cells Medium Enhanced P30626 +ENSG00000075151 EIF4G3 epididymis glandular cells Low Enhanced O43432 +ENSG00000075151 EIF4G3 prostate glandular cells Low Enhanced O43432 +ENSG00000075151 EIF4G3 seminal vesicle glandular cells Medium Enhanced O43432 +ENSG00000075151 EIF4G3 testis cells in seminiferous ducts High Enhanced O43432 +ENSG00000075151 EIF4G3 testis Leydig cells Low Enhanced O43432 +ENSG00000075188 NUP37 epididymis glandular cells Medium Enhanced Q8NFH4 +ENSG00000075188 NUP37 seminal vesicle glandular cells Low Enhanced Q8NFH4 +ENSG00000075188 NUP37 testis cells in seminiferous ducts Medium Enhanced Q8NFH4 +ENSG00000075188 NUP37 testis Leydig cells Low Enhanced Q8NFH4 +ENSG00000075239 ACAT1 epididymis glandular cells High Enhanced P24752 +ENSG00000075239 ACAT1 prostate glandular cells Medium Enhanced P24752 +ENSG00000075239 ACAT1 seminal vesicle glandular cells High Enhanced P24752 +ENSG00000075239 ACAT1 testis cells in seminiferous ducts Medium Enhanced P24752 +ENSG00000075239 ACAT1 testis Leydig cells High Enhanced P24752 +ENSG00000075292 ZNF638 epididymis glandular cells Medium Supported Q14966 +ENSG00000075292 ZNF638 prostate glandular cells Medium Supported Q14966 +ENSG00000075292 ZNF638 seminal vesicle glandular cells Medium Supported Q14966 +ENSG00000075292 ZNF638 testis cells in seminiferous ducts High Supported Q14966 +ENSG00000075292 ZNF638 testis Leydig cells Medium Supported Q14966 +ENSG00000075340 ADD2 testis cells in seminiferous ducts Low Enhanced P35612 +ENSG00000075391 RASAL2 seminal vesicle glandular cells Low Enhanced Q9UJF2 +ENSG00000075391 RASAL2 testis cells in seminiferous ducts High Enhanced Q9UJF2 +ENSG00000075391 RASAL2 testis Leydig cells Low Enhanced Q9UJF2 +ENSG00000075426 FOSL2 epididymis glandular cells Low Supported P15408 +ENSG00000075426 FOSL2 prostate glandular cells Low Supported P15408 +ENSG00000075539 FRYL epididymis glandular cells Medium Supported O94915 +ENSG00000075539 FRYL prostate glandular cells Low Supported O94915 +ENSG00000075539 FRYL seminal vesicle glandular cells Medium Supported O94915 +ENSG00000075539 FRYL testis cells in seminiferous ducts Medium Supported O94915 +ENSG00000075539 FRYL testis Leydig cells Medium Supported O94915 +ENSG00000075618 FSCN1 testis cells in seminiferous ducts High Enhanced Q16658 +ENSG00000075624 ACTB epididymis glandular cells High Supported P60709 +ENSG00000075624 ACTB testis cells in seminiferous ducts Medium Supported P60709 +ENSG00000075624 ACTB testis Leydig cells Low Supported P60709 +ENSG00000075651 PLD1 epididymis glandular cells Low Enhanced Q13393 +ENSG00000075651 PLD1 prostate glandular cells Low Enhanced Q13393 +ENSG00000075651 PLD1 seminal vesicle glandular cells Low Enhanced Q13393 +ENSG00000075651 PLD1 testis cells in seminiferous ducts Medium Enhanced Q13393 +ENSG00000075651 PLD1 testis Leydig cells Medium Enhanced Q13393 +ENSG00000075702 WDR62 epididymis glandular cells Low Enhanced O43379 +ENSG00000075702 WDR62 prostate glandular cells Low Enhanced O43379 +ENSG00000075702 WDR62 seminal vesicle glandular cells Low Enhanced O43379 +ENSG00000075702 WDR62 testis elongated or late spermatids High Enhanced O43379 +ENSG00000075702 WDR62 testis Leydig cells Low Enhanced O43379 +ENSG00000075702 WDR62 testis pachytene spermatocytes High Enhanced O43379 +ENSG00000075702 WDR62 testis preleptotene spermatocytes Low Enhanced O43379 +ENSG00000075702 WDR62 testis round or early spermatids High Enhanced O43379 +ENSG00000075702 WDR62 testis spermatogonia Low Enhanced O43379 +ENSG00000075711 DLG1 epididymis glandular cells High Supported Q12959 +ENSG00000075711 DLG1 prostate glandular cells High Supported Q12959 +ENSG00000075711 DLG1 seminal vesicle glandular cells High Supported Q12959 +ENSG00000075711 DLG1 testis cells in seminiferous ducts Low Supported Q12959 +ENSG00000075711 DLG1 testis Leydig cells Medium Supported Q12959 +ENSG00000075785 RAB7A epididymis glandular cells High Supported P51149 +ENSG00000075785 RAB7A prostate glandular cells High Supported P51149 +ENSG00000075785 RAB7A seminal vesicle glandular cells High Supported P51149 +ENSG00000075785 RAB7A testis cells in seminiferous ducts High Supported P51149 +ENSG00000075785 RAB7A testis Leydig cells High Supported P51149 +ENSG00000075790 BCAP29 epididymis glandular cells Medium Enhanced B7Z2L0 +ENSG00000075790 BCAP29 prostate glandular cells Medium Enhanced B7Z2L0 +ENSG00000075790 BCAP29 seminal vesicle glandular cells Medium Enhanced B7Z2L0 +ENSG00000075790 BCAP29 testis cells in seminiferous ducts High Enhanced B7Z2L0 +ENSG00000075790 BCAP29 testis Leydig cells Medium Enhanced B7Z2L0 +ENSG00000075891 PAX2 epididymis glandular cells High Enhanced Q02962 +ENSG00000075891 PAX2 seminal vesicle glandular cells Low Enhanced Q02962 +ENSG00000075891 PAX2 testis cells in seminiferous ducts Low Enhanced Q02962 +ENSG00000075945 KIFAP3 epididymis glandular cells Medium Supported Q92845 +ENSG00000075945 KIFAP3 prostate glandular cells Medium Supported Q92845 +ENSG00000075945 KIFAP3 seminal vesicle glandular cells Low Supported Q92845 +ENSG00000075945 KIFAP3 testis cells in seminiferous ducts Medium Supported Q92845 +ENSG00000075945 KIFAP3 testis Leydig cells High Supported Q92845 +ENSG00000075975 MKRN2 epididymis glandular cells Medium Enhanced Q9H000 +ENSG00000075975 MKRN2 prostate glandular cells Medium Enhanced Q9H000 +ENSG00000075975 MKRN2 seminal vesicle glandular cells Medium Enhanced Q9H000 +ENSG00000075975 MKRN2 testis cells in seminiferous ducts High Enhanced Q9H000 +ENSG00000075975 MKRN2 testis Leydig cells High Enhanced Q9H000 +ENSG00000076003 MCM6 prostate glandular cells Medium Enhanced Q14566 +ENSG00000076003 MCM6 testis cells in seminiferous ducts High Enhanced Q14566 +ENSG00000076043 REXO2 epididymis glandular cells Medium Enhanced Q9Y3B8 +ENSG00000076043 REXO2 prostate glandular cells High Enhanced Q9Y3B8 +ENSG00000076043 REXO2 seminal vesicle glandular cells Medium Enhanced Q9Y3B8 +ENSG00000076043 REXO2 testis cells in seminiferous ducts High Enhanced Q9Y3B8 +ENSG00000076043 REXO2 testis Leydig cells High Enhanced Q9Y3B8 +ENSG00000076053 RBM7 epididymis glandular cells Low Supported Q9Y580 +ENSG00000076053 RBM7 prostate glandular cells Low Supported Q9Y580 +ENSG00000076053 RBM7 seminal vesicle glandular cells Low Supported Q9Y580 +ENSG00000076053 RBM7 testis cells in seminiferous ducts High Supported Q9Y580 +ENSG00000076053 RBM7 testis Leydig cells Medium Supported Q9Y580 +ENSG00000076242 MLH1 epididymis glandular cells High Supported P40692 +ENSG00000076242 MLH1 prostate glandular cells Medium Supported P40692 +ENSG00000076242 MLH1 seminal vesicle glandular cells Medium Supported P40692 +ENSG00000076242 MLH1 testis cells in seminiferous ducts High Supported P40692 +ENSG00000076242 MLH1 testis Leydig cells High Supported P40692 +ENSG00000076513 ANKRD13A epididymis glandular cells Medium Enhanced Q8IZ07 +ENSG00000076513 ANKRD13A prostate glandular cells Low Enhanced Q8IZ07 +ENSG00000076513 ANKRD13A testis cells in seminiferous ducts Medium Enhanced Q8IZ07 +ENSG00000076513 ANKRD13A testis Leydig cells Medium Enhanced Q8IZ07 +ENSG00000076554 TPD52 epididymis glandular cells High Enhanced P55327 +ENSG00000076554 TPD52 prostate glandular cells High Enhanced P55327 +ENSG00000076554 TPD52 seminal vesicle glandular cells Medium Enhanced P55327 +ENSG00000076554 TPD52 testis cells in seminiferous ducts Low Enhanced P55327 +ENSG00000076555 ACACB testis cells in seminiferous ducts Medium Enhanced O00763 +ENSG00000076604 TRAF4 epididymis glandular cells Medium Enhanced Q9BUZ4 +ENSG00000076604 TRAF4 seminal vesicle glandular cells High Enhanced Q9BUZ4 +ENSG00000076604 TRAF4 testis cells in seminiferous ducts High Enhanced Q9BUZ4 +ENSG00000076770 MBNL3 epididymis glandular cells Low Enhanced Q9NUK0 +ENSG00000076770 MBNL3 testis cells in seminiferous ducts Low Enhanced Q9NUK0 +ENSG00000076826 CAMSAP3 epididymis glandular cells Low Enhanced Q9P1Y5 +ENSG00000076826 CAMSAP3 testis cells in seminiferous ducts Low Enhanced Q9P1Y5 +ENSG00000076826 CAMSAP3 testis Leydig cells Medium Enhanced Q9P1Y5 +ENSG00000076864 RAP1GAP epididymis glandular cells Low Enhanced P47736 +ENSG00000076864 RAP1GAP prostate glandular cells Medium Enhanced P47736 +ENSG00000076864 RAP1GAP testis cells in seminiferous ducts Low Enhanced P47736 +ENSG00000076928 ARHGEF1 epididymis glandular cells Low Enhanced Q92888 +ENSG00000076984 MAP2K7 epididymis glandular cells Medium Supported O14733 +ENSG00000076984 MAP2K7 prostate glandular cells Low Supported O14733 +ENSG00000076984 MAP2K7 seminal vesicle glandular cells Medium Supported O14733 +ENSG00000076984 MAP2K7 testis cells in seminiferous ducts Medium Supported O14733 +ENSG00000076984 MAP2K7 testis Leydig cells Low Supported O14733 +ENSG00000077063 CTTNBP2 epididymis glandular cells Medium Enhanced Q8WZ74 +ENSG00000077063 CTTNBP2 prostate glandular cells Low Enhanced Q8WZ74 +ENSG00000077063 CTTNBP2 seminal vesicle glandular cells Low Enhanced Q8WZ74 +ENSG00000077063 CTTNBP2 testis cells in seminiferous ducts Low Enhanced Q8WZ74 +ENSG00000077063 CTTNBP2 testis Leydig cells Low Enhanced Q8WZ74 +ENSG00000077092 RARB epididymis glandular cells Low Enhanced P10826 +ENSG00000077092 RARB prostate glandular cells Low Enhanced P10826 +ENSG00000077092 RARB seminal vesicle glandular cells Medium Enhanced P10826 +ENSG00000077092 RARB testis cells in seminiferous ducts Medium Enhanced P10826 +ENSG00000077092 RARB testis Leydig cells Low Enhanced P10826 +ENSG00000077097 TOP2B epididymis glandular cells High Supported Q02880 +ENSG00000077097 TOP2B prostate glandular cells Medium Supported Q02880 +ENSG00000077097 TOP2B seminal vesicle glandular cells Medium Supported Q02880 +ENSG00000077097 TOP2B testis cells in seminiferous ducts High Supported Q02880 +ENSG00000077097 TOP2B testis Leydig cells Medium Supported Q02880 +ENSG00000077150 NFKB2 testis cells in seminiferous ducts Medium Enhanced Q00653 +ENSG00000077150 NFKB2 testis Leydig cells Low Enhanced Q00653 +ENSG00000077238 IL4R epididymis glandular cells Low Enhanced P24394 +ENSG00000077238 IL4R seminal vesicle glandular cells Medium Enhanced P24394 +ENSG00000077238 IL4R testis cells in seminiferous ducts Low Enhanced P24394 +ENSG00000077238 IL4R testis Leydig cells Medium Enhanced P24394 +ENSG00000077312 SNRPA epididymis glandular cells Medium Enhanced P09012 +ENSG00000077312 SNRPA prostate glandular cells Medium Enhanced P09012 +ENSG00000077312 SNRPA seminal vesicle glandular cells Medium Enhanced P09012 +ENSG00000077312 SNRPA testis cells in seminiferous ducts Medium Enhanced P09012 +ENSG00000077312 SNRPA testis Leydig cells Medium Enhanced P09012 +ENSG00000077327 SPAG6 testis elongated or late spermatids Medium Enhanced O75602 +ENSG00000077327 SPAG6 testis Leydig cells Medium Enhanced O75602 +ENSG00000077327 SPAG6 testis pachytene spermatocytes Medium Enhanced O75602 +ENSG00000077327 SPAG6 testis round or early spermatids Medium Enhanced O75602 +ENSG00000077380 DYNC1I2 epididymis glandular cells High Enhanced Q13409 +ENSG00000077380 DYNC1I2 prostate glandular cells High Enhanced Q13409 +ENSG00000077380 DYNC1I2 seminal vesicle glandular cells High Enhanced Q13409 +ENSG00000077380 DYNC1I2 testis cells in seminiferous ducts High Enhanced Q13409 +ENSG00000077380 DYNC1I2 testis Leydig cells Medium Enhanced Q13409 +ENSG00000077454 LRCH4 epididymis glandular cells Low Enhanced O75427 +ENSG00000077454 LRCH4 prostate glandular cells Low Enhanced O75427 +ENSG00000077454 LRCH4 seminal vesicle glandular cells Low Enhanced O75427 +ENSG00000077454 LRCH4 testis cells in seminiferous ducts Medium Enhanced O75427 +ENSG00000077463 SIRT6 epididymis glandular cells High Supported Q8N6T7 +ENSG00000077463 SIRT6 prostate glandular cells Medium Supported Q8N6T7 +ENSG00000077463 SIRT6 seminal vesicle glandular cells High Supported Q8N6T7 +ENSG00000077463 SIRT6 testis cells in seminiferous ducts High Supported Q8N6T7 +ENSG00000077463 SIRT6 testis Leydig cells High Supported Q8N6T7 +ENSG00000077514 POLD3 prostate glandular cells Low Enhanced Q15054 +ENSG00000077514 POLD3 seminal vesicle glandular cells Medium Enhanced Q15054 +ENSG00000077514 POLD3 testis cells in seminiferous ducts High Enhanced Q15054 +ENSG00000077514 POLD3 testis Leydig cells Medium Enhanced Q15054 +ENSG00000077800 FKBP6 testis elongated or late spermatids Low Enhanced O75344 +ENSG00000077800 FKBP6 testis pachytene spermatocytes Low Enhanced O75344 +ENSG00000077800 FKBP6 testis preleptotene spermatocytes Medium Enhanced O75344 +ENSG00000077800 FKBP6 testis round or early spermatids Low Enhanced O75344 +ENSG00000077800 FKBP6 testis spermatogonia High Enhanced O75344 +ENSG00000077935 SMC1B testis elongated or late spermatids Low Enhanced Q8NDV3 +ENSG00000077935 SMC1B testis Leydig cells Low Enhanced Q8NDV3 +ENSG00000077935 SMC1B testis pachytene spermatocytes High Enhanced Q8NDV3 +ENSG00000077935 SMC1B testis preleptotene spermatocytes High Enhanced Q8NDV3 +ENSG00000077935 SMC1B testis round or early spermatids Medium Enhanced Q8NDV3 +ENSG00000077935 SMC1B testis spermatogonia High Enhanced Q8NDV3 +ENSG00000077942 FBLN1 prostate glandular cells High Enhanced P23142 +ENSG00000078043 PIAS2 seminal vesicle glandular cells Low Enhanced O75928 +ENSG00000078043 PIAS2 testis Leydig cells Low Enhanced O75928 +ENSG00000078043 PIAS2 testis pachytene spermatocytes Medium Enhanced O75928 +ENSG00000078043 PIAS2 testis preleptotene spermatocytes High Enhanced O75928 +ENSG00000078043 PIAS2 testis round or early spermatids Medium Enhanced O75928 +ENSG00000078043 PIAS2 testis spermatogonia High Enhanced O75928 +ENSG00000078140 UBE2K epididymis glandular cells Medium Supported P61086 +ENSG00000078140 UBE2K prostate glandular cells Medium Supported P61086 +ENSG00000078140 UBE2K seminal vesicle glandular cells Medium Supported P61086 +ENSG00000078140 UBE2K testis cells in seminiferous ducts Medium Supported P61086 +ENSG00000078140 UBE2K testis Leydig cells Medium Supported P61086 +ENSG00000078369 GNB1 epididymis glandular cells Medium Supported P62873 +ENSG00000078369 GNB1 seminal vesicle glandular cells Medium Supported P62873 +ENSG00000078369 GNB1 testis cells in seminiferous ducts Low Supported P62873 +ENSG00000078403 MLLT10 testis cells in seminiferous ducts High Supported P55197 +ENSG00000078549 ADCYAP1R1 testis Leydig cells Low Enhanced P41586 +ENSG00000078674 PCM1 epididymis glandular cells Medium Enhanced Q15154 +ENSG00000078674 PCM1 seminal vesicle glandular cells Medium Enhanced Q15154 +ENSG00000078674 PCM1 testis cells in seminiferous ducts High Enhanced Q15154 +ENSG00000078674 PCM1 testis Leydig cells Medium Enhanced Q15154 +ENSG00000078699 CBFA2T2 epididymis glandular cells Medium Enhanced O43439 +ENSG00000078699 CBFA2T2 prostate glandular cells Medium Enhanced O43439 +ENSG00000078699 CBFA2T2 seminal vesicle glandular cells Low Enhanced O43439 +ENSG00000078699 CBFA2T2 testis cells in seminiferous ducts Medium Enhanced O43439 +ENSG00000078699 CBFA2T2 testis Leydig cells Medium Enhanced O43439 +ENSG00000078747 ITCH epididymis glandular cells Medium Supported Q96J02 +ENSG00000078747 ITCH prostate glandular cells Medium Supported Q96J02 +ENSG00000078747 ITCH seminal vesicle glandular cells Medium Supported Q96J02 +ENSG00000078747 ITCH testis cells in seminiferous ducts Medium Supported Q96J02 +ENSG00000078747 ITCH testis Leydig cells Medium Supported Q96J02 +ENSG00000078808 SDF4 prostate glandular cells High Enhanced Q9BRK5 +ENSG00000078808 SDF4 seminal vesicle glandular cells Low Enhanced Q9BRK5 +ENSG00000078808 SDF4 testis cells in seminiferous ducts High Enhanced Q9BRK5 +ENSG00000078902 TOLLIP epididymis glandular cells High Enhanced Q9H0E2 +ENSG00000078902 TOLLIP prostate glandular cells Medium Enhanced Q9H0E2 +ENSG00000078902 TOLLIP seminal vesicle glandular cells Low Enhanced Q9H0E2 +ENSG00000078902 TOLLIP testis cells in seminiferous ducts Medium Enhanced Q9H0E2 +ENSG00000078902 TOLLIP testis Leydig cells Medium Enhanced Q9H0E2 +ENSG00000079101 CLUL1 testis cells in seminiferous ducts Low Supported Q15846 +ENSG00000079134 THOC1 epididymis glandular cells Low Enhanced Q96FV9 +ENSG00000079134 THOC1 prostate glandular cells Low Enhanced Q96FV9 +ENSG00000079134 THOC1 seminal vesicle glandular cells Low Enhanced Q96FV9 +ENSG00000079134 THOC1 testis cells in seminiferous ducts Medium Enhanced Q96FV9 +ENSG00000079134 THOC1 testis Leydig cells Low Enhanced Q96FV9 +ENSG00000079156 OSBPL6 epididymis glandular cells Low Enhanced Q9BZF3 +ENSG00000079246 XRCC5 epididymis glandular cells High Supported P13010 +ENSG00000079246 XRCC5 prostate glandular cells High Supported P13010 +ENSG00000079246 XRCC5 seminal vesicle glandular cells High Supported P13010 +ENSG00000079246 XRCC5 testis cells in seminiferous ducts High Supported P13010 +ENSG00000079246 XRCC5 testis Leydig cells High Supported P13010 +ENSG00000079332 SAR1A epididymis glandular cells High Supported Q9NR31 +ENSG00000079332 SAR1A prostate glandular cells Medium Supported Q9NR31 +ENSG00000079332 SAR1A seminal vesicle glandular cells Medium Supported Q9NR31 +ENSG00000079332 SAR1A testis cells in seminiferous ducts Medium Supported Q9NR31 +ENSG00000079332 SAR1A testis Leydig cells Medium Supported Q9NR31 +ENSG00000079385 CEACAM1 prostate glandular cells Low Enhanced P13688 +ENSG00000079691 CARMIL1 epididymis glandular cells Medium Enhanced Q5VZK9 +ENSG00000079691 CARMIL1 prostate glandular cells Low Enhanced Q5VZK9 +ENSG00000079691 CARMIL1 seminal vesicle glandular cells Medium Enhanced Q5VZK9 +ENSG00000079691 CARMIL1 testis cells in seminiferous ducts High Enhanced Q5VZK9 +ENSG00000079691 CARMIL1 testis Leydig cells Low Enhanced Q5VZK9 +ENSG00000079785 DDX1 epididymis glandular cells High Enhanced Q92499 +ENSG00000079785 DDX1 prostate glandular cells High Enhanced Q92499 +ENSG00000079785 DDX1 seminal vesicle glandular cells High Enhanced Q92499 +ENSG00000079785 DDX1 testis cells in seminiferous ducts High Enhanced Q92499 +ENSG00000079785 DDX1 testis Leydig cells High Enhanced Q92499 +ENSG00000079805 DNM2 epididymis glandular cells Medium Enhanced P50570 +ENSG00000079805 DNM2 prostate glandular cells Medium Enhanced P50570 +ENSG00000079805 DNM2 seminal vesicle glandular cells Medium Enhanced P50570 +ENSG00000079805 DNM2 testis cells in seminiferous ducts Medium Enhanced P50570 +ENSG00000079805 DNM2 testis Leydig cells Medium Enhanced P50570 +ENSG00000079819 EPB41L2 epididymis glandular cells Low Supported O43491 +ENSG00000079819 EPB41L2 seminal vesicle glandular cells Low Supported O43491 +ENSG00000079819 EPB41L2 testis cells in seminiferous ducts High Supported O43491 +ENSG00000079819 EPB41L2 testis Leydig cells Medium Supported O43491 +ENSG00000079950 STX7 epididymis glandular cells Medium Enhanced O15400 +ENSG00000079950 STX7 testis cells in seminiferous ducts Low Enhanced O15400 +ENSG00000079950 STX7 testis Leydig cells High Enhanced O15400 +ENSG00000080007 DDX43 testis cells in seminiferous ducts High Enhanced Q9NXZ2 +ENSG00000080007 DDX43 testis Leydig cells Low Enhanced Q9NXZ2 +ENSG00000080298 RFX3 epididymis glandular cells Medium Enhanced P48380 +ENSG00000080298 RFX3 prostate glandular cells Medium Enhanced P48380 +ENSG00000080298 RFX3 testis elongated or late spermatids Medium Enhanced P48380 +ENSG00000080298 RFX3 testis pachytene spermatocytes High Enhanced P48380 +ENSG00000080298 RFX3 testis round or early spermatids High Enhanced P48380 +ENSG00000080345 RIF1 epididymis glandular cells Medium Supported Q5UIP0 +ENSG00000080345 RIF1 prostate glandular cells Medium Supported Q5UIP0 +ENSG00000080345 RIF1 seminal vesicle glandular cells Medium Supported Q5UIP0 +ENSG00000080345 RIF1 testis cells in seminiferous ducts High Supported Q5UIP0 +ENSG00000080345 RIF1 testis Leydig cells Medium Supported Q5UIP0 +ENSG00000080493 SLC4A4 prostate glandular cells Low Enhanced Q9Y6R1 +ENSG00000080503 SMARCA2 epididymis glandular cells High Enhanced P51531 +ENSG00000080503 SMARCA2 prostate glandular cells Medium Enhanced P51531 +ENSG00000080503 SMARCA2 seminal vesicle glandular cells High Enhanced P51531 +ENSG00000080503 SMARCA2 testis cells in seminiferous ducts High Enhanced P51531 +ENSG00000080503 SMARCA2 testis Leydig cells Medium Enhanced P51531 +ENSG00000080572 PIH1D3 testis round or early spermatids High Enhanced Q9NQM4 +ENSG00000080839 RBL1 epididymis glandular cells Low Enhanced P28749 +ENSG00000080839 RBL1 seminal vesicle glandular cells Medium Enhanced P28749 +ENSG00000080839 RBL1 testis cells in seminiferous ducts Medium Enhanced P28749 +ENSG00000080839 RBL1 testis Leydig cells Medium Enhanced P28749 +ENSG00000081154 PCNP epididymis glandular cells High Supported Q8WW12 +ENSG00000081154 PCNP prostate glandular cells Medium Supported Q8WW12 +ENSG00000081154 PCNP seminal vesicle glandular cells High Supported Q8WW12 +ENSG00000081154 PCNP testis cells in seminiferous ducts Medium Supported Q8WW12 +ENSG00000081154 PCNP testis Leydig cells High Supported Q8WW12 +ENSG00000081181 ARG2 epididymis glandular cells Low Enhanced P78540 +ENSG00000081181 ARG2 prostate glandular cells High Enhanced P78540 +ENSG00000081181 ARG2 seminal vesicle glandular cells Low Enhanced P78540 +ENSG00000081189 MEF2C testis cells in seminiferous ducts Low Enhanced Q06413 +ENSG00000081189 MEF2C testis Leydig cells Medium Enhanced Q06413 +ENSG00000081320 STK17B epididymis glandular cells Medium Enhanced O94768 +ENSG00000081320 STK17B prostate glandular cells Low Enhanced O94768 +ENSG00000081320 STK17B seminal vesicle glandular cells Low Enhanced O94768 +ENSG00000081320 STK17B testis cells in seminiferous ducts Low Enhanced O94768 +ENSG00000081320 STK17B testis Leydig cells Medium Enhanced O94768 +ENSG00000081923 ATP8B1 epididymis glandular cells Medium Enhanced O43520 +ENSG00000081923 ATP8B1 prostate glandular cells Medium Enhanced O43520 +ENSG00000081923 ATP8B1 seminal vesicle glandular cells Low Enhanced O43520 +ENSG00000081923 ATP8B1 testis cells in seminiferous ducts Medium Enhanced O43520 +ENSG00000081923 ATP8B1 testis Leydig cells Medium Enhanced O43520 +ENSG00000082212 ME2 epididymis glandular cells Medium Enhanced P23368 +ENSG00000082212 ME2 prostate glandular cells High Enhanced P23368 +ENSG00000082212 ME2 seminal vesicle glandular cells High Enhanced P23368 +ENSG00000082212 ME2 testis cells in seminiferous ducts High Enhanced P23368 +ENSG00000082212 ME2 testis Leydig cells High Enhanced P23368 +ENSG00000082258 CCNT2 epididymis glandular cells High Supported O60583 +ENSG00000082258 CCNT2 prostate glandular cells High Supported O60583 +ENSG00000082258 CCNT2 seminal vesicle glandular cells High Supported O60583 +ENSG00000082258 CCNT2 testis cells in seminiferous ducts High Supported O60583 +ENSG00000082258 CCNT2 testis Leydig cells High Supported O60583 +ENSG00000082397 EPB41L3 epididymis glandular cells Low Enhanced Q9Y2J2 +ENSG00000082397 EPB41L3 testis cells in seminiferous ducts Medium Enhanced Q9Y2J2 +ENSG00000082438 COBLL1 epididymis glandular cells High Enhanced Q53SF7 +ENSG00000082438 COBLL1 prostate glandular cells High Enhanced Q53SF7 +ENSG00000082438 COBLL1 seminal vesicle glandular cells Medium Enhanced Q53SF7 +ENSG00000082438 COBLL1 testis cells in seminiferous ducts Low Enhanced Q53SF7 +ENSG00000082438 COBLL1 testis Leydig cells Medium Enhanced Q53SF7 +ENSG00000082512 TRAF5 epididymis glandular cells Low Enhanced O00463 +ENSG00000082512 TRAF5 prostate glandular cells Low Enhanced O00463 +ENSG00000082512 TRAF5 seminal vesicle glandular cells Low Enhanced O00463 +ENSG00000082512 TRAF5 testis Leydig cells Low Enhanced O00463 +ENSG00000082898 XPO1 epididymis glandular cells High Supported O14980 +ENSG00000082898 XPO1 prostate glandular cells Medium Supported O14980 +ENSG00000082898 XPO1 seminal vesicle glandular cells Medium Supported O14980 +ENSG00000082898 XPO1 testis cells in seminiferous ducts High Supported O14980 +ENSG00000082898 XPO1 testis Leydig cells High Supported O14980 +ENSG00000083097 DOPEY1 epididymis glandular cells Medium Enhanced Q5JWR5 +ENSG00000083097 DOPEY1 prostate glandular cells Low Enhanced Q5JWR5 +ENSG00000083097 DOPEY1 seminal vesicle glandular cells Medium Enhanced Q5JWR5 +ENSG00000083097 DOPEY1 testis cells in seminiferous ducts Medium Enhanced Q5JWR5 +ENSG00000083097 DOPEY1 testis Leydig cells Medium Enhanced Q5JWR5 +ENSG00000083168 KAT6A epididymis glandular cells Medium Supported Q92794 +ENSG00000083168 KAT6A prostate glandular cells Medium Supported Q92794 +ENSG00000083168 KAT6A seminal vesicle glandular cells Medium Supported Q92794 +ENSG00000083168 KAT6A testis cells in seminiferous ducts Medium Supported Q92794 +ENSG00000083168 KAT6A testis Leydig cells Medium Supported Q92794 +ENSG00000083642 PDS5B epididymis glandular cells High Supported Q9NTI5 +ENSG00000083642 PDS5B prostate glandular cells High Supported Q9NTI5 +ENSG00000083642 PDS5B seminal vesicle glandular cells Medium Supported Q9NTI5 +ENSG00000083642 PDS5B testis cells in seminiferous ducts High Supported Q9NTI5 +ENSG00000083642 PDS5B testis Leydig cells Medium Supported Q9NTI5 +ENSG00000083720 OXCT1 epididymis glandular cells Medium Enhanced P55809 +ENSG00000083720 OXCT1 prostate glandular cells High Enhanced P55809 +ENSG00000083720 OXCT1 seminal vesicle glandular cells High Enhanced P55809 +ENSG00000083720 OXCT1 testis cells in seminiferous ducts High Enhanced P55809 +ENSG00000083845 RPS5 epididymis glandular cells Medium Enhanced P46782 +ENSG00000083845 RPS5 prostate glandular cells Medium Enhanced P46782 +ENSG00000083845 RPS5 seminal vesicle glandular cells Medium Enhanced P46782 +ENSG00000083845 RPS5 testis cells in seminiferous ducts Medium Enhanced P46782 +ENSG00000083845 RPS5 testis Leydig cells Medium Enhanced P46782 +ENSG00000083896 YTHDC1 epididymis glandular cells High Supported NA +ENSG00000083896 YTHDC1 prostate glandular cells Medium Supported NA +ENSG00000083896 YTHDC1 seminal vesicle glandular cells Medium Supported NA +ENSG00000083896 YTHDC1 testis cells in seminiferous ducts High Supported NA +ENSG00000083896 YTHDC1 testis Leydig cells Medium Supported NA +ENSG00000084090 STARD7 epididymis glandular cells Medium Supported Q9NQZ5 +ENSG00000084090 STARD7 prostate glandular cells Medium Supported Q9NQZ5 +ENSG00000084090 STARD7 seminal vesicle glandular cells Medium Supported Q9NQZ5 +ENSG00000084090 STARD7 testis cells in seminiferous ducts Medium Supported Q9NQZ5 +ENSG00000084090 STARD7 testis Leydig cells Medium Supported Q9NQZ5 +ENSG00000084093 REST epididymis glandular cells Medium Supported Q13127 +ENSG00000084093 REST prostate glandular cells Medium Supported Q13127 +ENSG00000084093 REST seminal vesicle glandular cells Medium Supported Q13127 +ENSG00000084093 REST testis cells in seminiferous ducts Medium Supported Q13127 +ENSG00000084093 REST testis Leydig cells Medium Supported Q13127 +ENSG00000084110 HAL epididymis glandular cells Medium Enhanced P42357 +ENSG00000084110 HAL prostate glandular cells Medium Enhanced P42357 +ENSG00000084110 HAL seminal vesicle glandular cells Medium Enhanced P42357 +ENSG00000084110 HAL testis cells in seminiferous ducts Medium Enhanced P42357 +ENSG00000084110 HAL testis Leydig cells Medium Enhanced P42357 +ENSG00000084207 GSTP1 epididymis glandular cells High Enhanced P09211 +ENSG00000084207 GSTP1 prostate glandular cells Medium Enhanced P09211 +ENSG00000084207 GSTP1 seminal vesicle glandular cells High Enhanced P09211 +ENSG00000084207 GSTP1 testis Leydig cells Medium Enhanced P09211 +ENSG00000084623 EIF3I epididymis glandular cells High Enhanced Q13347 +ENSG00000084623 EIF3I prostate glandular cells High Enhanced Q13347 +ENSG00000084623 EIF3I seminal vesicle glandular cells High Enhanced Q13347 +ENSG00000084623 EIF3I testis cells in seminiferous ducts High Enhanced Q13347 +ENSG00000084623 EIF3I testis Leydig cells High Enhanced Q13347 +ENSG00000084652 TXLNA epididymis glandular cells High Enhanced P40222 +ENSG00000084652 TXLNA prostate glandular cells Medium Enhanced P40222 +ENSG00000084652 TXLNA seminal vesicle glandular cells Medium Enhanced P40222 +ENSG00000084652 TXLNA testis cells in seminiferous ducts High Enhanced P40222 +ENSG00000084652 TXLNA testis Leydig cells High Enhanced P40222 +ENSG00000084676 NCOA1 epididymis glandular cells Medium Enhanced Q15788 +ENSG00000084676 NCOA1 prostate glandular cells Medium Enhanced Q15788 +ENSG00000084676 NCOA1 seminal vesicle glandular cells Medium Enhanced Q15788 +ENSG00000084676 NCOA1 testis cells in seminiferous ducts High Enhanced Q15788 +ENSG00000084676 NCOA1 testis Leydig cells High Enhanced Q15788 +ENSG00000084774 CAD epididymis glandular cells Medium Supported P27708 +ENSG00000084774 CAD prostate glandular cells Low Supported P27708 +ENSG00000084774 CAD seminal vesicle glandular cells Low Supported P27708 +ENSG00000084774 CAD testis cells in seminiferous ducts High Supported P27708 +ENSG00000084774 CAD testis Leydig cells Medium Supported P27708 +ENSG00000085063 CD59 epididymis glandular cells Medium Supported P13987 +ENSG00000085063 CD59 prostate glandular cells Medium Supported P13987 +ENSG00000085063 CD59 seminal vesicle glandular cells Medium Supported P13987 +ENSG00000085063 CD59 testis cells in seminiferous ducts Low Supported P13987 +ENSG00000085063 CD59 testis Leydig cells Medium Supported P13987 +ENSG00000085224 ATRX epididymis glandular cells High Supported P46100 +ENSG00000085224 ATRX prostate glandular cells Medium Supported P46100 +ENSG00000085224 ATRX seminal vesicle glandular cells Medium Supported P46100 +ENSG00000085224 ATRX testis cells in seminiferous ducts Medium Supported P46100 +ENSG00000085224 ATRX testis Leydig cells High Supported P46100 +ENSG00000085231 AK6 epididymis glandular cells Medium Supported NA +ENSG00000085231 AK6 prostate glandular cells Medium Supported NA +ENSG00000085231 AK6 testis cells in seminiferous ducts High Supported NA +ENSG00000085231 AK6 testis Leydig cells Medium Supported NA +ENSG00000085276 MECOM epididymis glandular cells High Supported Q03112 +ENSG00000085276 MECOM prostate glandular cells High Supported Q03112 +ENSG00000085276 MECOM seminal vesicle glandular cells High Supported Q03112 +ENSG00000085276 MECOM testis cells in seminiferous ducts High Supported Q03112 +ENSG00000085276 MECOM testis Leydig cells High Supported Q03112 +ENSG00000085377 PREP epididymis glandular cells Medium Enhanced P48147 +ENSG00000085377 PREP prostate glandular cells Medium Enhanced P48147 +ENSG00000085377 PREP seminal vesicle glandular cells Medium Enhanced P48147 +ENSG00000085377 PREP testis cells in seminiferous ducts Medium Enhanced P48147 +ENSG00000085377 PREP testis Leydig cells Medium Enhanced P48147 +ENSG00000085491 SLC25A24 epididymis glandular cells High Enhanced NA +ENSG00000085491 SLC25A24 prostate glandular cells Medium Enhanced NA +ENSG00000085491 SLC25A24 seminal vesicle glandular cells Medium Enhanced NA +ENSG00000085491 SLC25A24 testis cells in seminiferous ducts Low Enhanced NA +ENSG00000085491 SLC25A24 testis Leydig cells High Enhanced NA +ENSG00000085662 AKR1B1 seminal vesicle glandular cells Medium Enhanced P15121 +ENSG00000085721 RRN3 epididymis glandular cells Medium Supported NA +ENSG00000085721 RRN3 prostate glandular cells Medium Supported NA +ENSG00000085721 RRN3 seminal vesicle glandular cells Medium Supported NA +ENSG00000085721 RRN3 testis cells in seminiferous ducts High Supported NA +ENSG00000085721 RRN3 testis Leydig cells High Supported NA +ENSG00000085733 CTTN epididymis glandular cells High Supported Q14247 +ENSG00000085733 CTTN prostate glandular cells Medium Supported Q14247 +ENSG00000085733 CTTN seminal vesicle glandular cells Medium Supported Q14247 +ENSG00000085733 CTTN testis cells in seminiferous ducts Medium Supported Q14247 +ENSG00000085733 CTTN testis Leydig cells Medium Supported Q14247 +ENSG00000085788 DDHD2 epididymis glandular cells Low Supported O94830 +ENSG00000085788 DDHD2 prostate glandular cells Low Supported O94830 +ENSG00000085788 DDHD2 testis cells in seminiferous ducts Medium Supported O94830 +ENSG00000085788 DDHD2 testis Leydig cells High Supported O94830 +ENSG00000085978 ATG16L1 epididymis glandular cells Medium Enhanced NA +ENSG00000085978 ATG16L1 prostate glandular cells Medium Enhanced NA +ENSG00000085978 ATG16L1 seminal vesicle glandular cells Medium Enhanced NA +ENSG00000085978 ATG16L1 testis cells in seminiferous ducts High Enhanced NA +ENSG00000085978 ATG16L1 testis Leydig cells Low Enhanced NA +ENSG00000086062 B4GALT1 epididymis glandular cells High Enhanced P15291 +ENSG00000086062 B4GALT1 prostate glandular cells High Enhanced P15291 +ENSG00000086062 B4GALT1 seminal vesicle glandular cells High Enhanced P15291 +ENSG00000086062 B4GALT1 testis cells in seminiferous ducts Low Enhanced P15291 +ENSG00000086062 B4GALT1 testis Leydig cells Medium Enhanced P15291 +ENSG00000086065 CHMP5 prostate glandular cells Medium Enhanced Q9NZZ3 +ENSG00000086065 CHMP5 seminal vesicle glandular cells Medium Enhanced Q9NZZ3 +ENSG00000086065 CHMP5 testis cells in seminiferous ducts Low Enhanced Q9NZZ3 +ENSG00000086205 FOLH1 prostate glandular cells High Enhanced Q04609 +ENSG00000086288 NME8 testis elongated or late spermatids High Supported Q8N427 +ENSG00000086288 NME8 testis Leydig cells Medium Supported Q8N427 +ENSG00000086288 NME8 testis pachytene spermatocytes Low Supported Q8N427 +ENSG00000086288 NME8 testis preleptotene spermatocytes Low Supported Q8N427 +ENSG00000086288 NME8 testis round or early spermatids High Supported Q8N427 +ENSG00000086288 NME8 testis sertoli cells Low Supported Q8N427 +ENSG00000086288 NME8 testis spermatogonia Medium Supported Q8N427 +ENSG00000086475 SEPHS1 epididymis glandular cells High Enhanced P49903 +ENSG00000086475 SEPHS1 prostate glandular cells High Enhanced P49903 +ENSG00000086475 SEPHS1 seminal vesicle glandular cells High Enhanced P49903 +ENSG00000086475 SEPHS1 testis cells in seminiferous ducts High Enhanced P49903 +ENSG00000086475 SEPHS1 testis Leydig cells High Enhanced P49903 +ENSG00000086504 MRPL28 epididymis glandular cells High Enhanced Q13084 +ENSG00000086504 MRPL28 prostate glandular cells High Enhanced Q13084 +ENSG00000086504 MRPL28 seminal vesicle glandular cells High Enhanced Q13084 +ENSG00000086504 MRPL28 testis cells in seminiferous ducts Medium Enhanced Q13084 +ENSG00000086504 MRPL28 testis Leydig cells High Enhanced Q13084 +ENSG00000086589 RBM22 epididymis glandular cells Medium Supported Q9NW64 +ENSG00000086589 RBM22 prostate glandular cells Medium Supported Q9NW64 +ENSG00000086589 RBM22 seminal vesicle glandular cells Medium Supported Q9NW64 +ENSG00000086589 RBM22 testis cells in seminiferous ducts Medium Supported Q9NW64 +ENSG00000086589 RBM22 testis Leydig cells High Supported Q9NW64 +ENSG00000086712 TXLNG epididymis glandular cells Medium Enhanced Q9NUQ3 +ENSG00000086712 TXLNG prostate glandular cells Medium Enhanced Q9NUQ3 +ENSG00000086712 TXLNG seminal vesicle glandular cells Medium Enhanced Q9NUQ3 +ENSG00000086712 TXLNG testis cells in seminiferous ducts Medium Enhanced Q9NUQ3 +ENSG00000086827 ZW10 epididymis glandular cells Medium Enhanced O43264 +ENSG00000086827 ZW10 prostate glandular cells High Enhanced O43264 +ENSG00000086827 ZW10 seminal vesicle glandular cells Medium Enhanced O43264 +ENSG00000086827 ZW10 testis cells in seminiferous ducts High Enhanced O43264 +ENSG00000086827 ZW10 testis Leydig cells High Enhanced O43264 +ENSG00000087086 FTL epididymis glandular cells Low Enhanced P02792 +ENSG00000087086 FTL prostate glandular cells Low Enhanced P02792 +ENSG00000087086 FTL testis cells in seminiferous ducts Low Enhanced P02792 +ENSG00000087086 FTL testis Leydig cells High Enhanced P02792 +ENSG00000087087 SRRT epididymis glandular cells High Supported Q9BXP5 +ENSG00000087087 SRRT prostate glandular cells Medium Supported Q9BXP5 +ENSG00000087087 SRRT seminal vesicle glandular cells High Supported Q9BXP5 +ENSG00000087087 SRRT testis cells in seminiferous ducts High Supported Q9BXP5 +ENSG00000087087 SRRT testis Leydig cells High Supported Q9BXP5 +ENSG00000087152 ATXN7L3 epididymis glandular cells High Supported Q14CW9 +ENSG00000087152 ATXN7L3 prostate glandular cells Medium Supported Q14CW9 +ENSG00000087152 ATXN7L3 seminal vesicle glandular cells Medium Supported Q14CW9 +ENSG00000087152 ATXN7L3 testis cells in seminiferous ducts High Supported Q14CW9 +ENSG00000087152 ATXN7L3 testis Leydig cells High Supported Q14CW9 +ENSG00000087191 PSMC5 epididymis glandular cells High Enhanced P62195 +ENSG00000087191 PSMC5 prostate glandular cells High Enhanced P62195 +ENSG00000087191 PSMC5 seminal vesicle glandular cells Medium Enhanced P62195 +ENSG00000087191 PSMC5 testis cells in seminiferous ducts High Enhanced P62195 +ENSG00000087191 PSMC5 testis Leydig cells High Enhanced P62195 +ENSG00000087206 UIMC1 testis cells in seminiferous ducts High Enhanced Q96RL1 +ENSG00000087206 UIMC1 testis Leydig cells Low Enhanced Q96RL1 +ENSG00000087253 LPCAT2 epididymis glandular cells High Enhanced Q7L5N7 +ENSG00000087253 LPCAT2 seminal vesicle glandular cells Medium Enhanced Q7L5N7 +ENSG00000087253 LPCAT2 testis cells in seminiferous ducts Low Enhanced Q7L5N7 +ENSG00000087253 LPCAT2 testis Leydig cells Medium Enhanced Q7L5N7 +ENSG00000087258 GNAO1 seminal vesicle glandular cells Low Enhanced P09471 +ENSG00000087274 ADD1 epididymis glandular cells Medium Enhanced P35611 +ENSG00000087274 ADD1 prostate glandular cells Medium Enhanced P35611 +ENSG00000087274 ADD1 seminal vesicle glandular cells Medium Enhanced P35611 +ENSG00000087274 ADD1 testis cells in seminiferous ducts Medium Enhanced P35611 +ENSG00000087274 ADD1 testis Leydig cells Medium Enhanced P35611 +ENSG00000087302 C14orf166 epididymis glandular cells High Supported Q9Y224 +ENSG00000087302 C14orf166 prostate glandular cells Medium Supported Q9Y224 +ENSG00000087302 C14orf166 seminal vesicle glandular cells Medium Supported Q9Y224 +ENSG00000087302 C14orf166 testis cells in seminiferous ducts High Supported Q9Y224 +ENSG00000087302 C14orf166 testis Leydig cells High Supported Q9Y224 +ENSG00000087303 NID2 epididymis glandular cells Medium Enhanced Q14112 +ENSG00000087303 NID2 prostate glandular cells Low Enhanced Q14112 +ENSG00000087303 NID2 testis Leydig cells Medium Enhanced Q14112 +ENSG00000087365 SF3B2 epididymis glandular cells High Supported Q13435 +ENSG00000087365 SF3B2 prostate glandular cells High Supported Q13435 +ENSG00000087365 SF3B2 seminal vesicle glandular cells Medium Supported Q13435 +ENSG00000087365 SF3B2 testis cells in seminiferous ducts High Supported Q13435 +ENSG00000087365 SF3B2 testis Leydig cells High Supported Q13435 +ENSG00000087470 DNM1L epididymis glandular cells Medium Enhanced O00429 +ENSG00000087470 DNM1L prostate glandular cells Medium Enhanced O00429 +ENSG00000087470 DNM1L seminal vesicle glandular cells Medium Enhanced O00429 +ENSG00000087470 DNM1L testis cells in seminiferous ducts Medium Enhanced O00429 +ENSG00000087470 DNM1L testis Leydig cells Medium Enhanced O00429 +ENSG00000087510 TFAP2C epididymis glandular cells Low Enhanced Q92754 +ENSG00000087510 TFAP2C seminal vesicle glandular cells Low Enhanced Q92754 +ENSG00000087842 PIR epididymis glandular cells Medium Enhanced O00625 +ENSG00000087842 PIR prostate glandular cells Medium Enhanced O00625 +ENSG00000087842 PIR seminal vesicle glandular cells Medium Enhanced O00625 +ENSG00000087842 PIR testis cells in seminiferous ducts Low Enhanced O00625 +ENSG00000087842 PIR testis Leydig cells Low Enhanced O00625 +ENSG00000087884 AAMDC epididymis glandular cells High Enhanced Q9H7C9 +ENSG00000087884 AAMDC prostate glandular cells Low Enhanced Q9H7C9 +ENSG00000087884 AAMDC seminal vesicle glandular cells High Enhanced Q9H7C9 +ENSG00000087884 AAMDC testis cells in seminiferous ducts Medium Enhanced Q9H7C9 +ENSG00000087884 AAMDC testis Leydig cells High Enhanced Q9H7C9 +ENSG00000087903 RFX2 testis pachytene spermatocytes High Enhanced P48378 +ENSG00000087903 RFX2 testis round or early spermatids High Enhanced P48378 +ENSG00000088247 KHSRP epididymis glandular cells High Enhanced Q92945 +ENSG00000088247 KHSRP prostate glandular cells Medium Enhanced Q92945 +ENSG00000088247 KHSRP seminal vesicle glandular cells High Enhanced Q92945 +ENSG00000088247 KHSRP testis cells in seminiferous ducts High Enhanced Q92945 +ENSG00000088247 KHSRP testis Leydig cells High Enhanced Q92945 +ENSG00000088305 DNMT3B epididymis glandular cells Medium Enhanced Q9UBC3 +ENSG00000088305 DNMT3B prostate glandular cells Low Enhanced Q9UBC3 +ENSG00000088305 DNMT3B testis cells in seminiferous ducts High Enhanced Q9UBC3 +ENSG00000088305 DNMT3B testis Leydig cells Medium Enhanced Q9UBC3 +ENSG00000088325 TPX2 epididymis glandular cells Medium Enhanced Q9ULW0 +ENSG00000088325 TPX2 seminal vesicle glandular cells Low Enhanced Q9ULW0 +ENSG00000088325 TPX2 testis cells in seminiferous ducts High Enhanced Q9ULW0 +ENSG00000088325 TPX2 testis Leydig cells Medium Enhanced Q9ULW0 +ENSG00000088367 EPB41L1 seminal vesicle glandular cells Medium Enhanced Q9H4G0 +ENSG00000088367 EPB41L1 testis Leydig cells Low Enhanced Q9H4G0 +ENSG00000088682 COQ9 epididymis glandular cells Medium Supported O75208 +ENSG00000088682 COQ9 prostate glandular cells Medium Supported O75208 +ENSG00000088682 COQ9 seminal vesicle glandular cells High Supported O75208 +ENSG00000088682 COQ9 testis cells in seminiferous ducts High Supported O75208 +ENSG00000088682 COQ9 testis Leydig cells High Supported O75208 +ENSG00000088726 TMEM40 testis Leydig cells Low Enhanced Q8WWA1 +ENSG00000088756 ARHGAP28 testis elongated or late spermatids High Enhanced Q9P2N2 +ENSG00000088756 ARHGAP28 testis Leydig cells Low Enhanced Q9P2N2 +ENSG00000088756 ARHGAP28 testis round or early spermatids High Enhanced Q9P2N2 +ENSG00000088833 NSFL1C epididymis glandular cells Medium Enhanced Q9UNZ2 +ENSG00000088833 NSFL1C prostate glandular cells High Enhanced Q9UNZ2 +ENSG00000088833 NSFL1C seminal vesicle glandular cells Medium Enhanced Q9UNZ2 +ENSG00000088833 NSFL1C testis cells in seminiferous ducts High Enhanced Q9UNZ2 +ENSG00000088833 NSFL1C testis Leydig cells High Enhanced Q9UNZ2 +ENSG00000088888 MAVS epididymis glandular cells High Enhanced Q7Z434 +ENSG00000088888 MAVS prostate glandular cells High Enhanced Q7Z434 +ENSG00000088888 MAVS seminal vesicle glandular cells High Enhanced Q7Z434 +ENSG00000088888 MAVS testis cells in seminiferous ducts High Enhanced Q7Z434 +ENSG00000088888 MAVS testis Leydig cells High Enhanced Q7Z434 +ENSG00000088930 XRN2 epididymis glandular cells High Supported Q9H0D6 +ENSG00000088930 XRN2 prostate glandular cells High Supported Q9H0D6 +ENSG00000088930 XRN2 seminal vesicle glandular cells High Supported Q9H0D6 +ENSG00000088930 XRN2 testis cells in seminiferous ducts High Supported Q9H0D6 +ENSG00000088930 XRN2 testis Leydig cells High Supported Q9H0D6 +ENSG00000088992 TESC epididymis glandular cells Medium Enhanced Q96BS2 +ENSG00000088992 TESC prostate glandular cells Medium Enhanced Q96BS2 +ENSG00000088992 TESC seminal vesicle glandular cells High Enhanced Q96BS2 +ENSG00000088992 TESC testis cells in seminiferous ducts Low Enhanced Q96BS2 +ENSG00000088992 TESC testis Leydig cells High Enhanced Q96BS2 +ENSG00000089022 MAPKAPK5 epididymis glandular cells Medium Supported Q8IW41 +ENSG00000089022 MAPKAPK5 prostate glandular cells Medium Supported Q8IW41 +ENSG00000089022 MAPKAPK5 seminal vesicle glandular cells Low Supported Q8IW41 +ENSG00000089022 MAPKAPK5 testis cells in seminiferous ducts Low Supported Q8IW41 +ENSG00000089022 MAPKAPK5 testis Leydig cells Medium Supported Q8IW41 +ENSG00000089048 ESF1 epididymis glandular cells High Supported Q9H501 +ENSG00000089048 ESF1 prostate glandular cells High Supported Q9H501 +ENSG00000089048 ESF1 seminal vesicle glandular cells High Supported Q9H501 +ENSG00000089048 ESF1 testis cells in seminiferous ducts High Supported Q9H501 +ENSG00000089048 ESF1 testis Leydig cells High Supported Q9H501 +ENSG00000089053 ANAPC5 epididymis glandular cells High Supported Q9UJX4 +ENSG00000089053 ANAPC5 prostate glandular cells Medium Supported Q9UJX4 +ENSG00000089053 ANAPC5 seminal vesicle glandular cells Medium Supported Q9UJX4 +ENSG00000089053 ANAPC5 testis cells in seminiferous ducts Medium Supported Q9UJX4 +ENSG00000089053 ANAPC5 testis Leydig cells High Supported Q9UJX4 +ENSG00000089154 GCN1 epididymis glandular cells High Enhanced Q92616 +ENSG00000089154 GCN1 prostate glandular cells Medium Enhanced Q92616 +ENSG00000089154 GCN1 seminal vesicle glandular cells Medium Enhanced Q92616 +ENSG00000089154 GCN1 testis cells in seminiferous ducts Medium Enhanced Q92616 +ENSG00000089154 GCN1 testis Leydig cells Medium Enhanced Q92616 +ENSG00000089159 PXN epididymis glandular cells High Enhanced P49023 +ENSG00000089159 PXN prostate glandular cells Medium Enhanced P49023 +ENSG00000089159 PXN seminal vesicle glandular cells High Enhanced P49023 +ENSG00000089159 PXN testis cells in seminiferous ducts Medium Enhanced P49023 +ENSG00000089159 PXN testis Leydig cells Low Enhanced P49023 +ENSG00000089163 SIRT4 epididymis glandular cells Medium Enhanced Q9Y6E7 +ENSG00000089163 SIRT4 prostate glandular cells Low Enhanced Q9Y6E7 +ENSG00000089163 SIRT4 seminal vesicle glandular cells Low Enhanced Q9Y6E7 +ENSG00000089163 SIRT4 testis cells in seminiferous ducts Medium Enhanced Q9Y6E7 +ENSG00000089163 SIRT4 testis Leydig cells Low Enhanced Q9Y6E7 +ENSG00000089199 CHGB prostate glandular cells Low Enhanced P05060 +ENSG00000089220 PEBP1 epididymis glandular cells Medium Enhanced P30086 +ENSG00000089220 PEBP1 prostate glandular cells Medium Enhanced P30086 +ENSG00000089220 PEBP1 seminal vesicle glandular cells Low Enhanced P30086 +ENSG00000089220 PEBP1 testis cells in seminiferous ducts Medium Enhanced P30086 +ENSG00000089220 PEBP1 testis Leydig cells High Enhanced P30086 +ENSG00000089248 ERP29 epididymis glandular cells High Enhanced P30040 +ENSG00000089248 ERP29 prostate glandular cells High Enhanced P30040 +ENSG00000089248 ERP29 seminal vesicle glandular cells High Enhanced P30040 +ENSG00000089248 ERP29 testis cells in seminiferous ducts High Enhanced P30040 +ENSG00000089248 ERP29 testis Leydig cells High Enhanced P30040 +ENSG00000089280 FUS epididymis glandular cells High Enhanced P35637 +ENSG00000089280 FUS prostate glandular cells High Enhanced P35637 +ENSG00000089280 FUS seminal vesicle glandular cells High Enhanced P35637 +ENSG00000089280 FUS testis cells in seminiferous ducts High Enhanced P35637 +ENSG00000089280 FUS testis Leydig cells High Enhanced P35637 +ENSG00000089356 FXYD3 epididymis glandular cells Low Enhanced Q14802 +ENSG00000089356 FXYD3 prostate glandular cells High Enhanced Q14802 +ENSG00000089356 FXYD3 seminal vesicle glandular cells Medium Enhanced Q14802 +ENSG00000089356 FXYD3 testis cells in seminiferous ducts Medium Enhanced Q14802 +ENSG00000089356 FXYD3 testis Leydig cells Medium Enhanced Q14802 +ENSG00000089597 GANAB epididymis glandular cells High Enhanced Q14697 +ENSG00000089597 GANAB prostate glandular cells Medium Enhanced Q14697 +ENSG00000089597 GANAB seminal vesicle glandular cells Medium Enhanced Q14697 +ENSG00000089597 GANAB testis cells in seminiferous ducts High Enhanced Q14697 +ENSG00000089597 GANAB testis Leydig cells Medium Enhanced Q14697 +ENSG00000089639 GMIP epididymis glandular cells Low Enhanced Q9P107 +ENSG00000089639 GMIP prostate glandular cells Medium Enhanced Q9P107 +ENSG00000089639 GMIP seminal vesicle glandular cells Low Enhanced Q9P107 +ENSG00000089639 GMIP testis cells in seminiferous ducts High Enhanced Q9P107 +ENSG00000089639 GMIP testis Leydig cells Low Enhanced Q9P107 +ENSG00000089685 BIRC5 testis Leydig cells Low Enhanced O15392 +ENSG00000089685 BIRC5 testis pachytene spermatocytes High Enhanced O15392 +ENSG00000089685 BIRC5 testis preleptotene spermatocytes High Enhanced O15392 +ENSG00000089685 BIRC5 testis round or early spermatids High Enhanced O15392 +ENSG00000089693 MLF2 epididymis glandular cells Medium Enhanced Q15773 +ENSG00000089693 MLF2 prostate glandular cells Medium Enhanced Q15773 +ENSG00000089693 MLF2 seminal vesicle glandular cells Medium Enhanced Q15773 +ENSG00000089693 MLF2 testis cells in seminiferous ducts High Enhanced Q15773 +ENSG00000089693 MLF2 testis Leydig cells High Enhanced Q15773 +ENSG00000089723 OTUB2 testis elongated or late spermatids High Enhanced NA +ENSG00000089723 OTUB2 testis Leydig cells Low Enhanced NA +ENSG00000089723 OTUB2 testis pachytene spermatocytes High Enhanced NA +ENSG00000089723 OTUB2 testis preleptotene spermatocytes Medium Enhanced NA +ENSG00000089723 OTUB2 testis round or early spermatids High Enhanced NA +ENSG00000089723 OTUB2 testis spermatogonia Low Enhanced NA +ENSG00000089820 ARHGAP4 epididymis glandular cells Low Enhanced P98171 +ENSG00000089820 ARHGAP4 seminal vesicle glandular cells Medium Enhanced P98171 +ENSG00000089820 ARHGAP4 testis cells in seminiferous ducts Low Enhanced P98171 +ENSG00000089902 RCOR1 epididymis glandular cells High Supported Q9UKL0 +ENSG00000089902 RCOR1 prostate glandular cells High Supported Q9UKL0 +ENSG00000089902 RCOR1 seminal vesicle glandular cells High Supported Q9UKL0 +ENSG00000089902 RCOR1 testis cells in seminiferous ducts High Supported Q9UKL0 +ENSG00000089902 RCOR1 testis Leydig cells Medium Supported Q9UKL0 +ENSG00000090013 BLVRB epididymis glandular cells High Enhanced P30043 +ENSG00000090013 BLVRB prostate glandular cells Medium Enhanced P30043 +ENSG00000090013 BLVRB seminal vesicle glandular cells Medium Enhanced P30043 +ENSG00000090013 BLVRB testis cells in seminiferous ducts Medium Enhanced P30043 +ENSG00000090013 BLVRB testis Leydig cells Medium Enhanced P30043 +ENSG00000090020 SLC9A1 epididymis glandular cells High Enhanced P19634 +ENSG00000090020 SLC9A1 prostate glandular cells High Enhanced P19634 +ENSG00000090020 SLC9A1 seminal vesicle glandular cells High Enhanced P19634 +ENSG00000090020 SLC9A1 testis Leydig cells Medium Enhanced P19634 +ENSG00000090054 SPTLC1 epididymis glandular cells Medium Supported O15269 +ENSG00000090054 SPTLC1 prostate glandular cells Medium Supported O15269 +ENSG00000090054 SPTLC1 seminal vesicle glandular cells Medium Supported O15269 +ENSG00000090054 SPTLC1 testis cells in seminiferous ducts Medium Supported O15269 +ENSG00000090054 SPTLC1 testis Leydig cells Medium Supported O15269 +ENSG00000090060 PAPOLA epididymis glandular cells High Supported P51003 +ENSG00000090060 PAPOLA prostate glandular cells Medium Supported P51003 +ENSG00000090060 PAPOLA seminal vesicle glandular cells Medium Supported P51003 +ENSG00000090060 PAPOLA testis cells in seminiferous ducts Medium Supported P51003 +ENSG00000090060 PAPOLA testis Leydig cells Medium Supported P51003 +ENSG00000090061 CCNK epididymis glandular cells High Enhanced O75909 +ENSG00000090061 CCNK prostate glandular cells Medium Enhanced O75909 +ENSG00000090061 CCNK seminal vesicle glandular cells Low Enhanced O75909 +ENSG00000090061 CCNK testis cells in seminiferous ducts High Enhanced O75909 +ENSG00000090061 CCNK testis Leydig cells High Enhanced O75909 +ENSG00000090273 NUDC epididymis glandular cells Medium Enhanced Q9Y266 +ENSG00000090273 NUDC prostate glandular cells Low Enhanced Q9Y266 +ENSG00000090273 NUDC seminal vesicle glandular cells Medium Enhanced Q9Y266 +ENSG00000090273 NUDC testis cells in seminiferous ducts Medium Enhanced Q9Y266 +ENSG00000090273 NUDC testis Leydig cells Medium Enhanced Q9Y266 +ENSG00000090339 ICAM1 testis cells in seminiferous ducts Low Enhanced P05362 +ENSG00000090372 STRN4 epididymis glandular cells Medium Enhanced Q9NRL3 +ENSG00000090372 STRN4 prostate glandular cells Medium Enhanced Q9NRL3 +ENSG00000090372 STRN4 seminal vesicle glandular cells Medium Enhanced Q9NRL3 +ENSG00000090372 STRN4 testis cells in seminiferous ducts High Enhanced Q9NRL3 +ENSG00000090372 STRN4 testis Leydig cells Medium Enhanced Q9NRL3 +ENSG00000090447 TFAP4 epididymis glandular cells Low Supported Q01664 +ENSG00000090447 TFAP4 prostate glandular cells Low Supported Q01664 +ENSG00000090447 TFAP4 seminal vesicle glandular cells Medium Supported Q01664 +ENSG00000090447 TFAP4 testis cells in seminiferous ducts Low Supported Q01664 +ENSG00000090512 FETUB epididymis glandular cells Medium Supported Q9UGM5 +ENSG00000090512 FETUB seminal vesicle glandular cells Low Supported Q9UGM5 +ENSG00000090512 FETUB testis cells in seminiferous ducts Low Supported Q9UGM5 +ENSG00000090512 FETUB testis Leydig cells High Supported Q9UGM5 +ENSG00000090520 DNAJB11 epididymis glandular cells High Supported Q9UBS4 +ENSG00000090520 DNAJB11 prostate glandular cells Medium Supported Q9UBS4 +ENSG00000090520 DNAJB11 seminal vesicle glandular cells Medium Supported Q9UBS4 +ENSG00000090520 DNAJB11 testis cells in seminiferous ducts High Supported Q9UBS4 +ENSG00000090520 DNAJB11 testis Leydig cells Medium Supported Q9UBS4 +ENSG00000090615 GOLGA3 epididymis glandular cells Medium Enhanced Q08378 +ENSG00000090615 GOLGA3 prostate glandular cells Medium Enhanced Q08378 +ENSG00000090615 GOLGA3 seminal vesicle glandular cells Medium Enhanced Q08378 +ENSG00000090615 GOLGA3 testis cells in seminiferous ducts Medium Enhanced Q08378 +ENSG00000090615 GOLGA3 testis Leydig cells Medium Enhanced Q08378 +ENSG00000090861 AARS epididymis glandular cells Low Supported P49588 +ENSG00000090861 AARS prostate glandular cells Low Supported P49588 +ENSG00000090861 AARS seminal vesicle glandular cells Medium Supported P49588 +ENSG00000090861 AARS testis cells in seminiferous ducts Medium Supported P49588 +ENSG00000090861 AARS testis Leydig cells Medium Supported P49588 +ENSG00000090863 GLG1 epididymis glandular cells High Supported Q92896 +ENSG00000090863 GLG1 prostate glandular cells High Supported Q92896 +ENSG00000090863 GLG1 seminal vesicle glandular cells Medium Supported Q92896 +ENSG00000090863 GLG1 testis cells in seminiferous ducts Low Supported Q92896 +ENSG00000090863 GLG1 testis Leydig cells High Supported Q92896 +ENSG00000091136 LAMB1 testis Leydig cells Low Enhanced P07942 +ENSG00000091140 DLD epididymis glandular cells Medium Enhanced P09622 +ENSG00000091140 DLD prostate glandular cells Medium Enhanced P09622 +ENSG00000091140 DLD seminal vesicle glandular cells High Enhanced P09622 +ENSG00000091140 DLD testis cells in seminiferous ducts High Enhanced P09622 +ENSG00000091140 DLD testis Leydig cells High Enhanced P09622 +ENSG00000091164 TXNL1 epididymis glandular cells Medium Supported O43396 +ENSG00000091164 TXNL1 prostate glandular cells Medium Supported O43396 +ENSG00000091164 TXNL1 seminal vesicle glandular cells Medium Supported O43396 +ENSG00000091164 TXNL1 testis cells in seminiferous ducts Medium Supported O43396 +ENSG00000091164 TXNL1 testis Leydig cells Medium Supported O43396 +ENSG00000091409 ITGA6 epididymis glandular cells Low Enhanced P23229 +ENSG00000091409 ITGA6 prostate glandular cells Low Enhanced P23229 +ENSG00000091409 ITGA6 seminal vesicle glandular cells Medium Enhanced P23229 +ENSG00000091409 ITGA6 testis cells in seminiferous ducts Low Enhanced P23229 +ENSG00000091483 FH epididymis glandular cells High Enhanced P07954 +ENSG00000091483 FH prostate glandular cells Medium Enhanced P07954 +ENSG00000091483 FH seminal vesicle glandular cells High Enhanced P07954 +ENSG00000091483 FH testis cells in seminiferous ducts Medium Enhanced P07954 +ENSG00000091483 FH testis Leydig cells High Enhanced P07954 +ENSG00000091513 TF testis cells in seminiferous ducts Low Enhanced P02787 +ENSG00000091513 TF testis Leydig cells Low Enhanced P02787 +ENSG00000091527 CDV3 epididymis glandular cells High Enhanced Q9UKY7 +ENSG00000091527 CDV3 prostate glandular cells Medium Enhanced Q9UKY7 +ENSG00000091527 CDV3 seminal vesicle glandular cells Medium Enhanced Q9UKY7 +ENSG00000091527 CDV3 testis cells in seminiferous ducts Medium Enhanced Q9UKY7 +ENSG00000091527 CDV3 testis Leydig cells Medium Enhanced Q9UKY7 +ENSG00000091592 NLRP1 epididymis glandular cells Low Enhanced Q9C000 +ENSG00000091592 NLRP1 prostate glandular cells Low Enhanced Q9C000 +ENSG00000091592 NLRP1 seminal vesicle glandular cells Low Enhanced Q9C000 +ENSG00000091592 NLRP1 testis cells in seminiferous ducts Low Enhanced Q9C000 +ENSG00000091592 NLRP1 testis Leydig cells Low Enhanced Q9C000 +ENSG00000091651 ORC6 epididymis glandular cells Medium Enhanced Q9Y5N6 +ENSG00000091651 ORC6 prostate glandular cells Low Enhanced Q9Y5N6 +ENSG00000091651 ORC6 seminal vesicle glandular cells Medium Enhanced Q9Y5N6 +ENSG00000091651 ORC6 testis Leydig cells Low Enhanced Q9Y5N6 +ENSG00000091651 ORC6 testis pachytene spermatocytes High Enhanced Q9Y5N6 +ENSG00000091651 ORC6 testis preleptotene spermatocytes High Enhanced Q9Y5N6 +ENSG00000091651 ORC6 testis spermatogonia Medium Enhanced Q9Y5N6 +ENSG00000091732 ZC3HC1 epididymis glandular cells Medium Enhanced Q86WB0 +ENSG00000091732 ZC3HC1 prostate glandular cells Medium Enhanced Q86WB0 +ENSG00000091732 ZC3HC1 seminal vesicle glandular cells Medium Enhanced Q86WB0 +ENSG00000091732 ZC3HC1 testis cells in seminiferous ducts Medium Enhanced Q86WB0 +ENSG00000091732 ZC3HC1 testis Leydig cells Medium Enhanced Q86WB0 +ENSG00000092199 HNRNPC epididymis glandular cells High Supported P07910 +ENSG00000092199 HNRNPC prostate glandular cells High Supported P07910 +ENSG00000092199 HNRNPC seminal vesicle glandular cells High Supported P07910 +ENSG00000092199 HNRNPC testis cells in seminiferous ducts High Supported P07910 +ENSG00000092199 HNRNPC testis Leydig cells High Supported P07910 +ENSG00000092200 RPGRIP1 testis cells in seminiferous ducts Low Enhanced Q96KN7 +ENSG00000092201 SUPT16H epididymis glandular cells Medium Enhanced Q9Y5B9 +ENSG00000092201 SUPT16H prostate glandular cells Low Enhanced Q9Y5B9 +ENSG00000092201 SUPT16H seminal vesicle glandular cells Low Enhanced Q9Y5B9 +ENSG00000092201 SUPT16H testis cells in seminiferous ducts High Enhanced Q9Y5B9 +ENSG00000092201 SUPT16H testis Leydig cells Medium Enhanced Q9Y5B9 +ENSG00000092208 GEMIN2 epididymis glandular cells Medium Enhanced O14893 +ENSG00000092208 GEMIN2 seminal vesicle glandular cells Low Enhanced O14893 +ENSG00000092208 GEMIN2 testis cells in seminiferous ducts High Enhanced O14893 +ENSG00000092208 GEMIN2 testis Leydig cells Low Enhanced O14893 +ENSG00000092345 DAZL testis pachytene spermatocytes Medium Enhanced Q92904 +ENSG00000092345 DAZL testis preleptotene spermatocytes High Enhanced Q92904 +ENSG00000092345 DAZL testis spermatogonia High Enhanced Q92904 +ENSG00000092529 CAPN3 seminal vesicle glandular cells Low Enhanced P20807 +ENSG00000092529 CAPN3 testis Leydig cells Low Enhanced P20807 +ENSG00000092621 PHGDH epididymis glandular cells High Enhanced O43175 +ENSG00000092621 PHGDH prostate glandular cells High Enhanced O43175 +ENSG00000092621 PHGDH seminal vesicle glandular cells High Enhanced O43175 +ENSG00000092621 PHGDH testis cells in seminiferous ducts High Enhanced O43175 +ENSG00000092621 PHGDH testis Leydig cells Medium Enhanced O43175 +ENSG00000092820 EZR epididymis glandular cells High Enhanced P15311 +ENSG00000092820 EZR prostate glandular cells Medium Enhanced P15311 +ENSG00000092820 EZR seminal vesicle glandular cells High Enhanced P15311 +ENSG00000092820 EZR testis cells in seminiferous ducts Medium Enhanced P15311 +ENSG00000092820 EZR testis Leydig cells Medium Enhanced P15311 +ENSG00000092964 DPYSL2 epididymis glandular cells Medium Supported Q16555 +ENSG00000092964 DPYSL2 seminal vesicle glandular cells Low Supported Q16555 +ENSG00000092964 DPYSL2 testis cells in seminiferous ducts Medium Supported Q16555 +ENSG00000092964 DPYSL2 testis Leydig cells Medium Supported Q16555 +ENSG00000093000 NUP50 epididymis glandular cells High Enhanced Q9UKX7 +ENSG00000093000 NUP50 prostate glandular cells High Enhanced Q9UKX7 +ENSG00000093000 NUP50 seminal vesicle glandular cells High Enhanced Q9UKX7 +ENSG00000093000 NUP50 testis cells in seminiferous ducts High Enhanced Q9UKX7 +ENSG00000093000 NUP50 testis Leydig cells High Enhanced Q9UKX7 +ENSG00000093009 CDC45 epididymis glandular cells Low Enhanced O75419 +ENSG00000093009 CDC45 prostate glandular cells Low Enhanced O75419 +ENSG00000093009 CDC45 testis elongated or late spermatids Low Enhanced O75419 +ENSG00000093009 CDC45 testis Leydig cells Low Enhanced O75419 +ENSG00000093009 CDC45 testis pachytene spermatocytes High Enhanced O75419 +ENSG00000093009 CDC45 testis peritubular cells Low Enhanced O75419 +ENSG00000093009 CDC45 testis preleptotene spermatocytes Low Enhanced O75419 +ENSG00000093009 CDC45 testis round or early spermatids Medium Enhanced O75419 +ENSG00000093009 CDC45 testis sertoli cells Low Enhanced O75419 +ENSG00000093009 CDC45 testis spermatogonia Low Enhanced O75419 +ENSG00000093010 COMT epididymis glandular cells High Enhanced P21964 +ENSG00000093010 COMT prostate glandular cells Medium Enhanced P21964 +ENSG00000093010 COMT seminal vesicle glandular cells Medium Enhanced P21964 +ENSG00000093010 COMT testis cells in seminiferous ducts High Enhanced P21964 +ENSG00000093010 COMT testis Leydig cells Low Enhanced P21964 +ENSG00000094916 CBX5 epididymis glandular cells Medium Enhanced P45973 +ENSG00000094916 CBX5 prostate glandular cells Low Enhanced P45973 +ENSG00000094916 CBX5 seminal vesicle glandular cells Medium Enhanced P45973 +ENSG00000094916 CBX5 testis cells in seminiferous ducts Medium Enhanced P45973 +ENSG00000094916 CBX5 testis Leydig cells Medium Enhanced P45973 +ENSG00000095002 MSH2 epididymis glandular cells Medium Supported P43246 +ENSG00000095002 MSH2 prostate glandular cells Medium Supported P43246 +ENSG00000095002 MSH2 seminal vesicle glandular cells Medium Supported P43246 +ENSG00000095002 MSH2 testis cells in seminiferous ducts Medium Supported P43246 +ENSG00000095002 MSH2 testis Leydig cells Medium Supported P43246 +ENSG00000095303 PTGS1 epididymis glandular cells Low Enhanced P23219 +ENSG00000095303 PTGS1 seminal vesicle glandular cells Medium Enhanced P23219 +ENSG00000095303 PTGS1 testis Leydig cells Low Enhanced P23219 +ENSG00000095321 CRAT epididymis glandular cells Low Enhanced P43155 +ENSG00000095321 CRAT prostate glandular cells Low Enhanced P43155 +ENSG00000095321 CRAT seminal vesicle glandular cells Low Enhanced P43155 +ENSG00000095321 CRAT testis cells in seminiferous ducts High Enhanced P43155 +ENSG00000095321 CRAT testis Leydig cells Low Enhanced P43155 +ENSG00000095370 SH2D3C testis Leydig cells Low Enhanced Q8N5H7 +ENSG00000095585 BLNK epididymis glandular cells Low Enhanced Q8WV28 +ENSG00000095627 TDRD1 testis cells in seminiferous ducts Medium Enhanced Q9BXT4 +ENSG00000095637 SORBS1 epididymis glandular cells Medium Enhanced Q9BX66 +ENSG00000095637 SORBS1 prostate glandular cells Low Enhanced Q9BX66 +ENSG00000095637 SORBS1 seminal vesicle glandular cells Low Enhanced Q9BX66 +ENSG00000095637 SORBS1 testis cells in seminiferous ducts Medium Enhanced Q9BX66 +ENSG00000095637 SORBS1 testis Leydig cells Low Enhanced Q9BX66 +ENSG00000095713 CRTAC1 epididymis glandular cells Medium Enhanced Q9NQ79 +ENSG00000095713 CRTAC1 seminal vesicle glandular cells Low Enhanced Q9NQ79 +ENSG00000095713 CRTAC1 testis Leydig cells Low Enhanced Q9NQ79 +ENSG00000095794 CREM epididymis glandular cells Medium Enhanced Q03060 +ENSG00000095794 CREM prostate glandular cells Low Enhanced Q03060 +ENSG00000095794 CREM seminal vesicle glandular cells Medium Enhanced Q03060 +ENSG00000095794 CREM testis cells in seminiferous ducts High Enhanced Q03060 +ENSG00000095794 CREM testis Leydig cells Medium Enhanced Q03060 +ENSG00000095932 SMIM24 epididymis glandular cells High Enhanced O75264 +ENSG00000095932 SMIM24 seminal vesicle glandular cells Low Enhanced O75264 +ENSG00000096006 CRISP3 seminal vesicle glandular cells Low Supported P54108 +ENSG00000096060 FKBP5 epididymis glandular cells High Enhanced Q13451 +ENSG00000096060 FKBP5 prostate glandular cells High Enhanced Q13451 +ENSG00000096060 FKBP5 seminal vesicle glandular cells High Enhanced Q13451 +ENSG00000096060 FKBP5 testis cells in seminiferous ducts High Enhanced Q13451 +ENSG00000096060 FKBP5 testis Leydig cells High Enhanced Q13451 +ENSG00000096384 HSP90AB1 epididymis glandular cells High Enhanced P08238 +ENSG00000096384 HSP90AB1 prostate glandular cells High Enhanced P08238 +ENSG00000096384 HSP90AB1 testis cells in seminiferous ducts High Enhanced P08238 +ENSG00000096384 HSP90AB1 testis Leydig cells Medium Enhanced P08238 +ENSG00000096401 CDC5L epididymis glandular cells High Supported Q99459 +ENSG00000096401 CDC5L prostate glandular cells Medium Supported Q99459 +ENSG00000096401 CDC5L seminal vesicle glandular cells High Supported Q99459 +ENSG00000096401 CDC5L testis cells in seminiferous ducts Medium Supported Q99459 +ENSG00000096401 CDC5L testis Leydig cells High Supported Q99459 +ENSG00000097007 ABL1 epididymis glandular cells Medium Supported P00519 +ENSG00000097007 ABL1 prostate glandular cells Low Supported P00519 +ENSG00000097007 ABL1 seminal vesicle glandular cells Medium Supported P00519 +ENSG00000097007 ABL1 testis cells in seminiferous ducts Medium Supported P00519 +ENSG00000097007 ABL1 testis Leydig cells Medium Supported P00519 +ENSG00000097021 ACOT7 epididymis glandular cells Low Enhanced O00154 +ENSG00000097021 ACOT7 testis cells in seminiferous ducts Medium Enhanced O00154 +ENSG00000097021 ACOT7 testis Leydig cells Medium Enhanced O00154 +ENSG00000097033 SH3GLB1 epididymis glandular cells Medium Enhanced Q9Y371 +ENSG00000097033 SH3GLB1 prostate glandular cells Medium Enhanced Q9Y371 +ENSG00000097033 SH3GLB1 seminal vesicle glandular cells Low Enhanced Q9Y371 +ENSG00000097033 SH3GLB1 testis cells in seminiferous ducts High Enhanced Q9Y371 +ENSG00000097033 SH3GLB1 testis Leydig cells Low Enhanced Q9Y371 +ENSG00000097046 CDC7 epididymis glandular cells Medium Enhanced O00311 +ENSG00000097046 CDC7 prostate glandular cells Low Enhanced O00311 +ENSG00000097046 CDC7 seminal vesicle glandular cells Low Enhanced O00311 +ENSG00000097046 CDC7 testis Leydig cells Low Enhanced O00311 +ENSG00000097046 CDC7 testis pachytene spermatocytes High Enhanced O00311 +ENSG00000097046 CDC7 testis preleptotene spermatocytes Medium Enhanced O00311 +ENSG00000097046 CDC7 testis round or early spermatids Medium Enhanced O00311 +ENSG00000097046 CDC7 testis spermatogonia Low Enhanced O00311 +ENSG00000099139 PCSK5 epididymis glandular cells Medium Enhanced Q92824 +ENSG00000099139 PCSK5 prostate glandular cells Low Enhanced Q92824 +ENSG00000099139 PCSK5 seminal vesicle glandular cells Medium Enhanced Q92824 +ENSG00000099139 PCSK5 testis cells in seminiferous ducts Low Enhanced Q92824 +ENSG00000099139 PCSK5 testis Leydig cells Low Enhanced Q92824 +ENSG00000099260 PALMD epididymis glandular cells Medium Supported Q9NP74 +ENSG00000099260 PALMD prostate glandular cells Medium Supported Q9NP74 +ENSG00000099260 PALMD seminal vesicle glandular cells Medium Supported Q9NP74 +ENSG00000099260 PALMD testis cells in seminiferous ducts Medium Supported Q9NP74 +ENSG00000099260 PALMD testis Leydig cells Medium Supported Q9NP74 +ENSG00000099284 H2AFY2 epididymis glandular cells Medium Enhanced Q9P0M6 +ENSG00000099284 H2AFY2 prostate glandular cells Medium Enhanced Q9P0M6 +ENSG00000099284 H2AFY2 seminal vesicle glandular cells Medium Enhanced Q9P0M6 +ENSG00000099284 H2AFY2 testis cells in seminiferous ducts Medium Enhanced Q9P0M6 +ENSG00000099284 H2AFY2 testis Leydig cells Low Enhanced Q9P0M6 +ENSG00000099290 WASHC2A epididymis glandular cells High Supported Q641Q2 +ENSG00000099290 WASHC2A prostate glandular cells High Supported Q641Q2 +ENSG00000099290 WASHC2A seminal vesicle glandular cells Medium Supported Q641Q2 +ENSG00000099290 WASHC2A testis cells in seminiferous ducts High Supported Q641Q2 +ENSG00000099290 WASHC2A testis Leydig cells Medium Supported Q641Q2 +ENSG00000099341 PSMD8 epididymis glandular cells Medium Enhanced P48556 +ENSG00000099341 PSMD8 prostate glandular cells Medium Enhanced P48556 +ENSG00000099341 PSMD8 seminal vesicle glandular cells Medium Enhanced P48556 +ENSG00000099341 PSMD8 testis cells in seminiferous ducts Medium Enhanced P48556 +ENSG00000099341 PSMD8 testis Leydig cells Low Enhanced P48556 +ENSG00000099381 SETD1A epididymis glandular cells Medium Enhanced O15047 +ENSG00000099381 SETD1A prostate glandular cells Low Enhanced O15047 +ENSG00000099381 SETD1A seminal vesicle glandular cells Medium Enhanced O15047 +ENSG00000099381 SETD1A testis cells in seminiferous ducts High Enhanced O15047 +ENSG00000099381 SETD1A testis Leydig cells Low Enhanced O15047 +ENSG00000099399 MAGEB2 testis cells in seminiferous ducts Medium Enhanced O15479 +ENSG00000099783 HNRNPM epididymis glandular cells High Supported P52272 +ENSG00000099783 HNRNPM prostate glandular cells High Supported P52272 +ENSG00000099783 HNRNPM seminal vesicle glandular cells High Supported P52272 +ENSG00000099783 HNRNPM testis cells in seminiferous ducts High Supported P52272 +ENSG00000099783 HNRNPM testis Leydig cells High Supported P52272 +ENSG00000099797 TECR epididymis glandular cells Low Supported Q9NZ01 +ENSG00000099797 TECR seminal vesicle glandular cells Medium Supported Q9NZ01 +ENSG00000099797 TECR testis cells in seminiferous ducts Low Supported Q9NZ01 +ENSG00000099797 TECR testis Leydig cells Medium Supported Q9NZ01 +ENSG00000099814 CEP170B epididymis glandular cells Medium Enhanced Q9Y4F5 +ENSG00000099814 CEP170B testis cells in seminiferous ducts Medium Enhanced Q9Y4F5 +ENSG00000099817 POLR2E epididymis glandular cells Medium Supported P19388 +ENSG00000099817 POLR2E prostate glandular cells Medium Supported P19388 +ENSG00000099817 POLR2E seminal vesicle glandular cells Medium Supported P19388 +ENSG00000099817 POLR2E testis cells in seminiferous ducts High Supported P19388 +ENSG00000099817 POLR2E testis Leydig cells High Supported P19388 +ENSG00000099834 CDHR5 epididymis glandular cells Medium Enhanced Q9HBB8 +ENSG00000099840 IZUMO4 testis elongated or late spermatids High Enhanced Q1ZYL8 +ENSG00000099840 IZUMO4 testis Leydig cells Low Enhanced Q1ZYL8 +ENSG00000099840 IZUMO4 testis pachytene spermatocytes Medium Enhanced Q1ZYL8 +ENSG00000099840 IZUMO4 testis preleptotene spermatocytes Low Enhanced Q1ZYL8 +ENSG00000099840 IZUMO4 testis round or early spermatids High Enhanced Q1ZYL8 +ENSG00000099840 IZUMO4 testis spermatogonia Medium Enhanced Q1ZYL8 +ENSG00000099875 MKNK2 epididymis glandular cells High Enhanced Q9HBH9 +ENSG00000099875 MKNK2 prostate glandular cells Medium Enhanced Q9HBH9 +ENSG00000099875 MKNK2 seminal vesicle glandular cells Medium Enhanced Q9HBH9 +ENSG00000099875 MKNK2 testis cells in seminiferous ducts High Enhanced Q9HBH9 +ENSG00000099875 MKNK2 testis Leydig cells High Enhanced Q9HBH9 +ENSG00000099889 ARVCF epididymis glandular cells High Enhanced O00192 +ENSG00000099889 ARVCF prostate glandular cells Low Enhanced O00192 +ENSG00000099889 ARVCF seminal vesicle glandular cells Low Enhanced O00192 +ENSG00000099901 RANBP1 epididymis glandular cells Medium Enhanced P43487 +ENSG00000099901 RANBP1 testis cells in seminiferous ducts High Enhanced P43487 +ENSG00000099940 SNAP29 epididymis glandular cells Medium Supported O95721 +ENSG00000099940 SNAP29 prostate glandular cells Medium Supported O95721 +ENSG00000099940 SNAP29 seminal vesicle glandular cells Medium Supported O95721 +ENSG00000099940 SNAP29 testis cells in seminiferous ducts High Supported O95721 +ENSG00000099940 SNAP29 testis Leydig cells Medium Supported O95721 +ENSG00000099956 SMARCB1 epididymis glandular cells High Supported A0A0U1RRB8 +ENSG00000099956 SMARCB1 prostate glandular cells High Supported A0A0U1RRB8 +ENSG00000099956 SMARCB1 seminal vesicle glandular cells High Supported A0A0U1RRB8 +ENSG00000099956 SMARCB1 testis cells in seminiferous ducts High Supported A0A0U1RRB8 +ENSG00000099956 SMARCB1 testis Leydig cells High Supported A0A0U1RRB8 +ENSG00000099960 SLC7A4 testis elongated or late spermatids High Enhanced O43246 +ENSG00000099960 SLC7A4 testis Leydig cells Low Enhanced O43246 +ENSG00000099960 SLC7A4 testis sertoli cells Medium Enhanced O43246 +ENSG00000099994 SUSD2 epididymis glandular cells Medium Enhanced Q9UGT4 +ENSG00000099994 SUSD2 prostate glandular cells Low Enhanced Q9UGT4 +ENSG00000099994 SUSD2 seminal vesicle glandular cells Medium Enhanced Q9UGT4 +ENSG00000099994 SUSD2 testis cells in seminiferous ducts Low Enhanced Q9UGT4 +ENSG00000099994 SUSD2 testis Leydig cells Medium Enhanced Q9UGT4 +ENSG00000099995 SF3A1 epididymis glandular cells High Enhanced Q15459 +ENSG00000099995 SF3A1 prostate glandular cells High Enhanced Q15459 +ENSG00000099995 SF3A1 seminal vesicle glandular cells High Enhanced Q15459 +ENSG00000099995 SF3A1 testis cells in seminiferous ducts High Enhanced Q15459 +ENSG00000099995 SF3A1 testis Leydig cells Medium Enhanced Q15459 +ENSG00000100023 PPIL2 epididymis glandular cells High Supported Q13356 +ENSG00000100023 PPIL2 prostate glandular cells Medium Supported Q13356 +ENSG00000100023 PPIL2 seminal vesicle glandular cells High Supported Q13356 +ENSG00000100023 PPIL2 testis cells in seminiferous ducts High Supported Q13356 +ENSG00000100023 PPIL2 testis Leydig cells High Supported Q13356 +ENSG00000100028 SNRPD3 epididymis glandular cells High Supported P62318 +ENSG00000100028 SNRPD3 prostate glandular cells High Supported P62318 +ENSG00000100028 SNRPD3 seminal vesicle glandular cells Medium Supported P62318 +ENSG00000100028 SNRPD3 testis cells in seminiferous ducts High Supported P62318 +ENSG00000100028 SNRPD3 testis Leydig cells High Supported P62318 +ENSG00000100029 PES1 epididymis glandular cells Low Supported O00541 +ENSG00000100029 PES1 prostate glandular cells Low Supported O00541 +ENSG00000100029 PES1 seminal vesicle glandular cells Medium Supported O00541 +ENSG00000100029 PES1 testis Leydig cells Low Supported O00541 +ENSG00000100031 GGT1 epididymis glandular cells Medium Supported P19440 +ENSG00000100056 DGCR14 epididymis glandular cells High Enhanced Q96DF8 +ENSG00000100056 DGCR14 prostate glandular cells High Enhanced Q96DF8 +ENSG00000100056 DGCR14 seminal vesicle glandular cells High Enhanced Q96DF8 +ENSG00000100056 DGCR14 testis cells in seminiferous ducts Medium Enhanced Q96DF8 +ENSG00000100056 DGCR14 testis Leydig cells Low Enhanced Q96DF8 +ENSG00000100083 GGA1 epididymis glandular cells Medium Supported Q9UJY5 +ENSG00000100083 GGA1 prostate glandular cells Medium Supported Q9UJY5 +ENSG00000100083 GGA1 seminal vesicle glandular cells Medium Supported Q9UJY5 +ENSG00000100083 GGA1 testis cells in seminiferous ducts Medium Supported Q9UJY5 +ENSG00000100083 GGA1 testis Leydig cells High Supported Q9UJY5 +ENSG00000100084 HIRA epididymis glandular cells High Enhanced P54198 +ENSG00000100084 HIRA prostate glandular cells High Enhanced P54198 +ENSG00000100084 HIRA seminal vesicle glandular cells High Enhanced P54198 +ENSG00000100084 HIRA testis cells in seminiferous ducts High Enhanced P54198 +ENSG00000100084 HIRA testis Leydig cells High Enhanced P54198 +ENSG00000100092 SH3BP1 epididymis glandular cells High Enhanced Q9Y3L3 +ENSG00000100092 SH3BP1 prostate glandular cells Medium Enhanced Q9Y3L3 +ENSG00000100092 SH3BP1 seminal vesicle glandular cells Medium Enhanced Q9Y3L3 +ENSG00000100092 SH3BP1 testis cells in seminiferous ducts High Enhanced Q9Y3L3 +ENSG00000100097 LGALS1 testis cells in seminiferous ducts Low Enhanced P09382 +ENSG00000100106 TRIOBP epididymis glandular cells Low Enhanced Q9H2D6 +ENSG00000100106 TRIOBP prostate glandular cells Medium Enhanced Q9H2D6 +ENSG00000100106 TRIOBP seminal vesicle glandular cells Low Enhanced Q9H2D6 +ENSG00000100106 TRIOBP testis cells in seminiferous ducts Low Enhanced Q9H2D6 +ENSG00000100106 TRIOBP testis Leydig cells High Enhanced Q9H2D6 +ENSG00000100142 POLR2F epididymis glandular cells Medium Supported P61218 +ENSG00000100142 POLR2F prostate glandular cells High Supported P61218 +ENSG00000100142 POLR2F seminal vesicle glandular cells Medium Supported P61218 +ENSG00000100142 POLR2F testis cells in seminiferous ducts High Supported P61218 +ENSG00000100142 POLR2F testis Leydig cells Medium Supported P61218 +ENSG00000100162 CENPM epididymis glandular cells Low Enhanced Q9NSP4 +ENSG00000100162 CENPM prostate glandular cells Low Enhanced Q9NSP4 +ENSG00000100162 CENPM seminal vesicle glandular cells Low Enhanced Q9NSP4 +ENSG00000100162 CENPM testis cells in seminiferous ducts Low Enhanced Q9NSP4 +ENSG00000100162 CENPM testis Leydig cells Low Enhanced Q9NSP4 +ENSG00000100170 SLC5A1 epididymis glandular cells Low Enhanced P13866 +ENSG00000100201 DDX17 epididymis glandular cells Medium Enhanced Q92841 +ENSG00000100201 DDX17 prostate glandular cells Low Enhanced Q92841 +ENSG00000100201 DDX17 seminal vesicle glandular cells Low Enhanced Q92841 +ENSG00000100201 DDX17 testis cells in seminiferous ducts High Enhanced Q92841 +ENSG00000100201 DDX17 testis Leydig cells Medium Enhanced Q92841 +ENSG00000100206 DMC1 testis pachytene spermatocytes High Enhanced Q14565 +ENSG00000100216 TOMM22 epididymis glandular cells High Enhanced Q9NS69 +ENSG00000100216 TOMM22 prostate glandular cells High Enhanced Q9NS69 +ENSG00000100216 TOMM22 seminal vesicle glandular cells High Enhanced Q9NS69 +ENSG00000100216 TOMM22 testis cells in seminiferous ducts High Enhanced Q9NS69 +ENSG00000100216 TOMM22 testis Leydig cells High Enhanced Q9NS69 +ENSG00000100220 RTCB epididymis glandular cells Medium Enhanced Q9Y3I0 +ENSG00000100220 RTCB prostate glandular cells Medium Enhanced Q9Y3I0 +ENSG00000100220 RTCB seminal vesicle glandular cells Medium Enhanced Q9Y3I0 +ENSG00000100220 RTCB testis cells in seminiferous ducts Medium Enhanced Q9Y3I0 +ENSG00000100220 RTCB testis Leydig cells Medium Enhanced Q9Y3I0 +ENSG00000100242 SUN2 epididymis glandular cells High Supported Q9UH99 +ENSG00000100242 SUN2 prostate glandular cells High Supported Q9UH99 +ENSG00000100242 SUN2 seminal vesicle glandular cells High Supported Q9UH99 +ENSG00000100242 SUN2 testis cells in seminiferous ducts Low Supported Q9UH99 +ENSG00000100242 SUN2 testis Leydig cells Low Supported Q9UH99 +ENSG00000100266 PACSIN2 epididymis glandular cells Medium Enhanced Q9UNF0 +ENSG00000100266 PACSIN2 prostate glandular cells Medium Enhanced Q9UNF0 +ENSG00000100266 PACSIN2 seminal vesicle glandular cells Medium Enhanced Q9UNF0 +ENSG00000100266 PACSIN2 testis cells in seminiferous ducts Medium Enhanced Q9UNF0 +ENSG00000100266 PACSIN2 testis Leydig cells Medium Enhanced Q9UNF0 +ENSG00000100285 NEFH prostate glandular cells Medium Enhanced P12036 +ENSG00000100297 MCM5 epididymis glandular cells Low Enhanced P33992 +ENSG00000100297 MCM5 prostate glandular cells Medium Enhanced P33992 +ENSG00000100297 MCM5 testis cells in seminiferous ducts Medium Enhanced P33992 +ENSG00000100299 ARSA epididymis glandular cells Medium Enhanced P15289 +ENSG00000100299 ARSA prostate glandular cells High Enhanced P15289 +ENSG00000100299 ARSA seminal vesicle glandular cells High Enhanced P15289 +ENSG00000100299 ARSA testis cells in seminiferous ducts Medium Enhanced P15289 +ENSG00000100299 ARSA testis Leydig cells Medium Enhanced P15289 +ENSG00000100302 RASD2 epididymis glandular cells Low Enhanced Q96D21 +ENSG00000100302 RASD2 prostate glandular cells Medium Enhanced Q96D21 +ENSG00000100302 RASD2 seminal vesicle glandular cells High Enhanced Q96D21 +ENSG00000100302 RASD2 testis cells in seminiferous ducts Low Enhanced Q96D21 +ENSG00000100302 RASD2 testis Leydig cells Low Enhanced Q96D21 +ENSG00000100307 CBX7 epididymis glandular cells Medium Enhanced O95931 +ENSG00000100307 CBX7 prostate glandular cells Low Enhanced O95931 +ENSG00000100307 CBX7 seminal vesicle glandular cells Medium Enhanced O95931 +ENSG00000100311 PDGFB epididymis glandular cells Medium Supported P01127 +ENSG00000100311 PDGFB prostate glandular cells Medium Supported P01127 +ENSG00000100311 PDGFB seminal vesicle glandular cells High Supported P01127 +ENSG00000100311 PDGFB testis cells in seminiferous ducts Medium Supported P01127 +ENSG00000100311 PDGFB testis Leydig cells Medium Supported P01127 +ENSG00000100312 ACR testis elongated or late spermatids High Enhanced E9PLV5 +ENSG00000100312 ACR testis Leydig cells Low Enhanced E9PLV5 +ENSG00000100312 ACR testis pachytene spermatocytes Medium Enhanced E9PLV5 +ENSG00000100312 ACR testis round or early spermatids High Enhanced E9PLV5 +ENSG00000100320 RBFOX2 epididymis glandular cells Low Enhanced B0QYY7 +ENSG00000100320 RBFOX2 prostate glandular cells Low Enhanced B0QYY7 +ENSG00000100320 RBFOX2 seminal vesicle glandular cells Medium Enhanced B0QYY7 +ENSG00000100320 RBFOX2 testis cells in seminiferous ducts Low Enhanced B0QYY7 +ENSG00000100320 RBFOX2 testis Leydig cells Low Enhanced B0QYY7 +ENSG00000100321 SYNGR1 epididymis glandular cells Low Enhanced O43759 +ENSG00000100321 SYNGR1 prostate glandular cells Low Enhanced O43759 +ENSG00000100321 SYNGR1 testis cells in seminiferous ducts Medium Enhanced O43759 +ENSG00000100321 SYNGR1 testis Leydig cells Medium Enhanced O43759 +ENSG00000100345 MYH9 epididymis glandular cells Medium Enhanced P35579 +ENSG00000100345 MYH9 prostate glandular cells Low Enhanced P35579 +ENSG00000100345 MYH9 seminal vesicle glandular cells High Enhanced P35579 +ENSG00000100345 MYH9 testis Leydig cells Low Enhanced P35579 +ENSG00000100347 SAMM50 epididymis glandular cells Medium Enhanced Q9Y512 +ENSG00000100347 SAMM50 prostate glandular cells Medium Enhanced Q9Y512 +ENSG00000100347 SAMM50 seminal vesicle glandular cells High Enhanced Q9Y512 +ENSG00000100347 SAMM50 testis cells in seminiferous ducts Medium Enhanced Q9Y512 +ENSG00000100347 SAMM50 testis Leydig cells High Enhanced Q9Y512 +ENSG00000100373 UPK3A epididymis glandular cells Low Enhanced O75631 +ENSG00000100380 ST13 epididymis glandular cells Medium Enhanced P50502 +ENSG00000100380 ST13 prostate glandular cells Medium Enhanced P50502 +ENSG00000100380 ST13 seminal vesicle glandular cells High Enhanced P50502 +ENSG00000100380 ST13 testis cells in seminiferous ducts High Enhanced P50502 +ENSG00000100380 ST13 testis Leydig cells High Enhanced P50502 +ENSG00000100393 EP300 epididymis glandular cells Medium Supported Q09472 +ENSG00000100393 EP300 prostate glandular cells Medium Supported Q09472 +ENSG00000100393 EP300 seminal vesicle glandular cells Medium Supported Q09472 +ENSG00000100393 EP300 testis cells in seminiferous ducts Medium Supported Q09472 +ENSG00000100393 EP300 testis Leydig cells Low Supported Q09472 +ENSG00000100401 RANGAP1 epididymis glandular cells High Enhanced P46060 +ENSG00000100401 RANGAP1 prostate glandular cells High Enhanced P46060 +ENSG00000100401 RANGAP1 seminal vesicle glandular cells High Enhanced P46060 +ENSG00000100401 RANGAP1 testis cells in seminiferous ducts High Enhanced P46060 +ENSG00000100401 RANGAP1 testis Leydig cells High Enhanced P46060 +ENSG00000100410 PHF5A epididymis glandular cells High Supported Q7RTV0 +ENSG00000100410 PHF5A prostate glandular cells Medium Supported Q7RTV0 +ENSG00000100410 PHF5A seminal vesicle glandular cells Medium Supported Q7RTV0 +ENSG00000100410 PHF5A testis cells in seminiferous ducts High Supported Q7RTV0 +ENSG00000100410 PHF5A testis Leydig cells Medium Supported Q7RTV0 +ENSG00000100412 ACO2 epididymis glandular cells High Enhanced Q99798 +ENSG00000100412 ACO2 prostate glandular cells High Enhanced Q99798 +ENSG00000100412 ACO2 seminal vesicle glandular cells High Enhanced Q99798 +ENSG00000100412 ACO2 testis cells in seminiferous ducts High Enhanced Q99798 +ENSG00000100412 ACO2 testis Leydig cells High Enhanced Q99798 +ENSG00000100429 HDAC10 epididymis glandular cells High Supported Q969S8 +ENSG00000100429 HDAC10 prostate glandular cells Medium Supported Q969S8 +ENSG00000100429 HDAC10 seminal vesicle glandular cells High Supported Q969S8 +ENSG00000100429 HDAC10 testis cells in seminiferous ducts High Supported Q969S8 +ENSG00000100429 HDAC10 testis Leydig cells Medium Supported Q969S8 +ENSG00000100442 FKBP3 epididymis glandular cells High Supported Q00688 +ENSG00000100442 FKBP3 prostate glandular cells High Supported Q00688 +ENSG00000100442 FKBP3 seminal vesicle glandular cells High Supported Q00688 +ENSG00000100442 FKBP3 testis cells in seminiferous ducts High Supported Q00688 +ENSG00000100442 FKBP3 testis Leydig cells Medium Supported Q00688 +ENSG00000100503 NIN epididymis glandular cells Medium Enhanced Q8N4C6 +ENSG00000100503 NIN prostate glandular cells Medium Enhanced Q8N4C6 +ENSG00000100503 NIN seminal vesicle glandular cells Low Enhanced Q8N4C6 +ENSG00000100503 NIN testis cells in seminiferous ducts Medium Enhanced Q8N4C6 +ENSG00000100503 NIN testis Leydig cells Medium Enhanced Q8N4C6 +ENSG00000100504 PYGL seminal vesicle glandular cells Medium Enhanced P06737 +ENSG00000100504 PYGL testis cells in seminiferous ducts Low Enhanced P06737 +ENSG00000100504 PYGL testis Leydig cells Low Enhanced P06737 +ENSG00000100523 DDHD1 prostate glandular cells Low Enhanced Q8NEL9 +ENSG00000100523 DDHD1 seminal vesicle glandular cells Low Enhanced Q8NEL9 +ENSG00000100523 DDHD1 testis elongated or late spermatids High Enhanced Q8NEL9 +ENSG00000100523 DDHD1 testis Leydig cells Low Enhanced Q8NEL9 +ENSG00000100523 DDHD1 testis pachytene spermatocytes Low Enhanced Q8NEL9 +ENSG00000100523 DDHD1 testis preleptotene spermatocytes High Enhanced Q8NEL9 +ENSG00000100523 DDHD1 testis round or early spermatids High Enhanced Q8NEL9 +ENSG00000100523 DDHD1 testis spermatogonia High Enhanced Q8NEL9 +ENSG00000100554 ATP6V1D epididymis glandular cells Low Enhanced Q9Y5K8 +ENSG00000100554 ATP6V1D prostate glandular cells Low Enhanced Q9Y5K8 +ENSG00000100558 PLEK2 epididymis glandular cells Low Enhanced Q9NYT0 +ENSG00000100558 PLEK2 prostate glandular cells Low Enhanced Q9NYT0 +ENSG00000100558 PLEK2 seminal vesicle glandular cells Low Enhanced Q9NYT0 +ENSG00000100558 PLEK2 testis cells in seminiferous ducts Low Enhanced Q9NYT0 +ENSG00000100558 PLEK2 testis Leydig cells Low Enhanced Q9NYT0 +ENSG00000100583 SAMD15 epididymis glandular cells Medium Enhanced Q9P1V8 +ENSG00000100583 SAMD15 prostate glandular cells Medium Enhanced Q9P1V8 +ENSG00000100583 SAMD15 seminal vesicle glandular cells Medium Enhanced Q9P1V8 +ENSG00000100583 SAMD15 testis cells in seminiferous ducts High Enhanced Q9P1V8 +ENSG00000100583 SAMD15 testis Leydig cells Low Enhanced Q9P1V8 +ENSG00000100591 AHSA1 epididymis glandular cells Medium Supported O95433 +ENSG00000100591 AHSA1 prostate glandular cells Medium Supported O95433 +ENSG00000100591 AHSA1 seminal vesicle glandular cells Medium Supported O95433 +ENSG00000100591 AHSA1 testis cells in seminiferous ducts High Supported O95433 +ENSG00000100591 AHSA1 testis Leydig cells Medium Supported O95433 +ENSG00000100600 LGMN epididymis glandular cells Medium Enhanced Q99538 +ENSG00000100600 LGMN prostate glandular cells Medium Enhanced Q99538 +ENSG00000100600 LGMN seminal vesicle glandular cells Medium Enhanced Q99538 +ENSG00000100600 LGMN testis cells in seminiferous ducts Low Enhanced Q99538 +ENSG00000100600 LGMN testis Leydig cells Low Enhanced Q99538 +ENSG00000100603 SNW1 epididymis glandular cells High Supported Q13573 +ENSG00000100603 SNW1 prostate glandular cells High Supported Q13573 +ENSG00000100603 SNW1 seminal vesicle glandular cells High Supported Q13573 +ENSG00000100603 SNW1 testis cells in seminiferous ducts High Supported Q13573 +ENSG00000100603 SNW1 testis Leydig cells High Supported Q13573 +ENSG00000100644 HIF1A epididymis glandular cells Medium Supported Q16665 +ENSG00000100644 HIF1A seminal vesicle glandular cells Low Supported Q16665 +ENSG00000100644 HIF1A testis cells in seminiferous ducts Low Supported Q16665 +ENSG00000100664 EIF5 epididymis glandular cells High Supported P55010 +ENSG00000100664 EIF5 prostate glandular cells High Supported P55010 +ENSG00000100664 EIF5 seminal vesicle glandular cells Medium Supported P55010 +ENSG00000100664 EIF5 testis cells in seminiferous ducts High Supported P55010 +ENSG00000100664 EIF5 testis Leydig cells High Supported P55010 +ENSG00000100722 ZC3H14 epididymis glandular cells Medium Enhanced Q6PJT7 +ENSG00000100722 ZC3H14 prostate glandular cells Low Enhanced Q6PJT7 +ENSG00000100722 ZC3H14 seminal vesicle glandular cells Low Enhanced Q6PJT7 +ENSG00000100722 ZC3H14 testis cells in seminiferous ducts Medium Enhanced Q6PJT7 +ENSG00000100722 ZC3H14 testis Leydig cells Medium Enhanced Q6PJT7 +ENSG00000100749 VRK1 epididymis glandular cells Low Enhanced Q99986 +ENSG00000100749 VRK1 testis cells in seminiferous ducts High Enhanced Q99986 +ENSG00000100811 YY1 epididymis glandular cells Medium Supported P25490 +ENSG00000100811 YY1 prostate glandular cells Low Supported P25490 +ENSG00000100811 YY1 seminal vesicle glandular cells Medium Supported P25490 +ENSG00000100811 YY1 testis Leydig cells Low Supported P25490 +ENSG00000100813 ACIN1 epididymis glandular cells Medium Supported Q9UKV3 +ENSG00000100813 ACIN1 prostate glandular cells Medium Supported Q9UKV3 +ENSG00000100813 ACIN1 seminal vesicle glandular cells Medium Supported Q9UKV3 +ENSG00000100813 ACIN1 testis cells in seminiferous ducts Medium Supported Q9UKV3 +ENSG00000100813 ACIN1 testis Leydig cells Medium Supported Q9UKV3 +ENSG00000100815 TRIP11 epididymis glandular cells High Supported Q15643 +ENSG00000100815 TRIP11 prostate glandular cells Medium Supported Q15643 +ENSG00000100815 TRIP11 seminal vesicle glandular cells Medium Supported Q15643 +ENSG00000100815 TRIP11 testis cells in seminiferous ducts High Supported Q15643 +ENSG00000100815 TRIP11 testis Leydig cells High Supported Q15643 +ENSG00000100823 APEX1 epididymis glandular cells High Enhanced P27695 +ENSG00000100823 APEX1 prostate glandular cells Medium Enhanced P27695 +ENSG00000100823 APEX1 seminal vesicle glandular cells Medium Enhanced P27695 +ENSG00000100823 APEX1 testis cells in seminiferous ducts Medium Enhanced P27695 +ENSG00000100823 APEX1 testis Leydig cells High Enhanced P27695 +ENSG00000100836 PABPN1 epididymis glandular cells High Supported Q86U42 +ENSG00000100836 PABPN1 prostate glandular cells High Supported Q86U42 +ENSG00000100836 PABPN1 seminal vesicle glandular cells High Supported Q86U42 +ENSG00000100836 PABPN1 testis cells in seminiferous ducts High Supported Q86U42 +ENSG00000100836 PABPN1 testis Leydig cells Medium Supported Q86U42 +ENSG00000100889 PCK2 seminal vesicle glandular cells Low Enhanced Q16822 +ENSG00000100926 TM9SF1 epididymis glandular cells High Supported O15321 +ENSG00000100926 TM9SF1 prostate glandular cells High Supported O15321 +ENSG00000100926 TM9SF1 seminal vesicle glandular cells High Supported O15321 +ENSG00000100926 TM9SF1 testis cells in seminiferous ducts Medium Supported O15321 +ENSG00000100926 TM9SF1 testis Leydig cells Medium Supported O15321 +ENSG00000100941 PNN epididymis glandular cells High Supported Q9H307 +ENSG00000100941 PNN prostate glandular cells Medium Supported Q9H307 +ENSG00000100941 PNN seminal vesicle glandular cells High Supported Q9H307 +ENSG00000100941 PNN testis cells in seminiferous ducts High Supported Q9H307 +ENSG00000100941 PNN testis Leydig cells Medium Supported Q9H307 +ENSG00000100982 PCIF1 epididymis glandular cells Medium Enhanced Q9H4Z3 +ENSG00000100982 PCIF1 prostate glandular cells Medium Enhanced Q9H4Z3 +ENSG00000100982 PCIF1 seminal vesicle glandular cells Medium Enhanced Q9H4Z3 +ENSG00000100982 PCIF1 testis cells in seminiferous ducts High Enhanced Q9H4Z3 +ENSG00000100982 PCIF1 testis Leydig cells Medium Enhanced Q9H4Z3 +ENSG00000100983 GSS epididymis glandular cells High Enhanced P48637 +ENSG00000100983 GSS prostate glandular cells Medium Enhanced P48637 +ENSG00000100983 GSS seminal vesicle glandular cells Medium Enhanced P48637 +ENSG00000100983 GSS testis cells in seminiferous ducts Low Enhanced P48637 +ENSG00000100983 GSS testis Leydig cells Low Enhanced P48637 +ENSG00000101000 PROCR epididymis glandular cells Low Enhanced Q9UNN8 +ENSG00000101000 PROCR seminal vesicle glandular cells Low Enhanced Q9UNN8 +ENSG00000101052 IFT52 epididymis glandular cells Medium Enhanced Q9Y366 +ENSG00000101052 IFT52 seminal vesicle glandular cells Low Enhanced Q9Y366 +ENSG00000101052 IFT52 testis cells in seminiferous ducts Medium Enhanced Q9Y366 +ENSG00000101052 IFT52 testis Leydig cells Low Enhanced Q9Y366 +ENSG00000101074 R3HDML testis cells in seminiferous ducts Medium Enhanced Q9H3Y0 +ENSG00000101076 HNF4A testis cells in seminiferous ducts Low Enhanced P41235 +ENSG00000101096 NFATC2 epididymis glandular cells Medium Enhanced Q13469 +ENSG00000101096 NFATC2 testis cells in seminiferous ducts Medium Enhanced Q13469 +ENSG00000101115 SALL4 testis preleptotene spermatocytes Low Enhanced Q9UJQ4 +ENSG00000101115 SALL4 testis spermatogonia High Enhanced Q9UJQ4 +ENSG00000101126 ADNP epididymis glandular cells High Supported Q9H2P0 +ENSG00000101126 ADNP prostate glandular cells Medium Supported Q9H2P0 +ENSG00000101126 ADNP seminal vesicle glandular cells Medium Supported Q9H2P0 +ENSG00000101126 ADNP testis cells in seminiferous ducts High Supported Q9H2P0 +ENSG00000101126 ADNP testis Leydig cells Medium Supported Q9H2P0 +ENSG00000101138 CSTF1 epididymis glandular cells High Enhanced Q05048 +ENSG00000101138 CSTF1 prostate glandular cells Medium Enhanced Q05048 +ENSG00000101138 CSTF1 seminal vesicle glandular cells Medium Enhanced Q05048 +ENSG00000101138 CSTF1 testis cells in seminiferous ducts High Enhanced Q05048 +ENSG00000101138 CSTF1 testis Leydig cells Medium Enhanced Q05048 +ENSG00000101160 CTSZ epididymis glandular cells Low Supported Q9UBR2 +ENSG00000101160 CTSZ prostate glandular cells Medium Supported Q9UBR2 +ENSG00000101160 CTSZ seminal vesicle glandular cells Medium Supported Q9UBR2 +ENSG00000101160 CTSZ testis cells in seminiferous ducts Medium Supported Q9UBR2 +ENSG00000101160 CTSZ testis Leydig cells Low Supported Q9UBR2 +ENSG00000101161 PRPF6 epididymis glandular cells Medium Enhanced O94906 +ENSG00000101161 PRPF6 prostate glandular cells Low Enhanced O94906 +ENSG00000101161 PRPF6 seminal vesicle glandular cells Medium Enhanced O94906 +ENSG00000101161 PRPF6 testis cells in seminiferous ducts High Enhanced O94906 +ENSG00000101161 PRPF6 testis Leydig cells High Enhanced O94906 +ENSG00000101182 PSMA7 epididymis glandular cells High Enhanced O14818 +ENSG00000101182 PSMA7 prostate glandular cells Medium Enhanced O14818 +ENSG00000101182 PSMA7 seminal vesicle glandular cells Medium Enhanced O14818 +ENSG00000101182 PSMA7 testis cells in seminiferous ducts High Enhanced O14818 +ENSG00000101182 PSMA7 testis Leydig cells High Enhanced O14818 +ENSG00000101189 MRGBP testis pachytene spermatocytes High Enhanced Q9NV56 +ENSG00000101189 MRGBP testis round or early spermatids High Enhanced Q9NV56 +ENSG00000101191 DIDO1 epididymis glandular cells High Supported Q9BTC0 +ENSG00000101191 DIDO1 prostate glandular cells High Supported Q9BTC0 +ENSG00000101191 DIDO1 seminal vesicle glandular cells High Supported Q9BTC0 +ENSG00000101191 DIDO1 testis cells in seminiferous ducts High Supported Q9BTC0 +ENSG00000101191 DIDO1 testis Leydig cells High Supported Q9BTC0 +ENSG00000101222 SPEF1 testis sertoli cells High Enhanced Q9Y4P9 +ENSG00000101224 CDC25B epididymis glandular cells Low Enhanced P30305 +ENSG00000101224 CDC25B testis Leydig cells Low Enhanced P30305 +ENSG00000101266 CSNK2A1 epididymis glandular cells Medium Enhanced P68400 +ENSG00000101266 CSNK2A1 prostate glandular cells Medium Enhanced P68400 +ENSG00000101266 CSNK2A1 seminal vesicle glandular cells Medium Enhanced P68400 +ENSG00000101266 CSNK2A1 testis cells in seminiferous ducts High Enhanced P68400 +ENSG00000101266 CSNK2A1 testis Leydig cells High Enhanced P68400 +ENSG00000101333 PLCB4 epididymis glandular cells Medium Supported Q15147 +ENSG00000101333 PLCB4 prostate glandular cells Low Supported Q15147 +ENSG00000101333 PLCB4 testis cells in seminiferous ducts Medium Supported Q15147 +ENSG00000101333 PLCB4 testis Leydig cells Medium Supported Q15147 +ENSG00000101347 SAMHD1 epididymis glandular cells Medium Enhanced Q9Y3Z3 +ENSG00000101347 SAMHD1 seminal vesicle glandular cells Medium Enhanced Q9Y3Z3 +ENSG00000101347 SAMHD1 testis cells in seminiferous ducts High Enhanced Q9Y3Z3 +ENSG00000101347 SAMHD1 testis Leydig cells High Enhanced Q9Y3Z3 +ENSG00000101361 NOP56 epididymis glandular cells Low Enhanced O00567 +ENSG00000101361 NOP56 prostate glandular cells Low Enhanced O00567 +ENSG00000101361 NOP56 seminal vesicle glandular cells Low Enhanced O00567 +ENSG00000101361 NOP56 testis cells in seminiferous ducts Medium Enhanced O00567 +ENSG00000101361 NOP56 testis Leydig cells Medium Enhanced O00567 +ENSG00000101365 IDH3B epididymis glandular cells High Enhanced O43837 +ENSG00000101365 IDH3B prostate glandular cells High Enhanced O43837 +ENSG00000101365 IDH3B seminal vesicle glandular cells High Enhanced O43837 +ENSG00000101365 IDH3B testis cells in seminiferous ducts High Enhanced O43837 +ENSG00000101365 IDH3B testis Leydig cells High Enhanced O43837 +ENSG00000101367 MAPRE1 epididymis glandular cells Medium Enhanced Q15691 +ENSG00000101367 MAPRE1 prostate glandular cells Low Enhanced Q15691 +ENSG00000101367 MAPRE1 seminal vesicle glandular cells Medium Enhanced Q15691 +ENSG00000101367 MAPRE1 testis cells in seminiferous ducts Medium Enhanced Q15691 +ENSG00000101367 MAPRE1 testis Leydig cells Low Enhanced Q15691 +ENSG00000101384 JAG1 epididymis glandular cells Medium Enhanced P78504 +ENSG00000101384 JAG1 prostate glandular cells Medium Enhanced P78504 +ENSG00000101384 JAG1 seminal vesicle glandular cells Medium Enhanced P78504 +ENSG00000101384 JAG1 testis cells in seminiferous ducts Low Enhanced P78504 +ENSG00000101384 JAG1 testis Leydig cells Medium Enhanced P78504 +ENSG00000101405 OXT testis cells in seminiferous ducts Medium Supported P01178 +ENSG00000101405 OXT testis Leydig cells Medium Supported P01178 +ENSG00000101412 E2F1 epididymis glandular cells Medium Enhanced Q01094 +ENSG00000101412 E2F1 prostate glandular cells Medium Enhanced Q01094 +ENSG00000101412 E2F1 seminal vesicle glandular cells Medium Enhanced Q01094 +ENSG00000101412 E2F1 testis cells in seminiferous ducts High Enhanced Q01094 +ENSG00000101412 E2F1 testis Leydig cells Medium Enhanced Q01094 +ENSG00000101413 RPRD1B epididymis glandular cells Medium Supported Q9NQG5 +ENSG00000101413 RPRD1B prostate glandular cells Medium Supported Q9NQG5 +ENSG00000101413 RPRD1B seminal vesicle glandular cells Medium Supported Q9NQG5 +ENSG00000101413 RPRD1B testis cells in seminiferous ducts Medium Supported Q9NQG5 +ENSG00000101413 RPRD1B testis Leydig cells Medium Supported Q9NQG5 +ENSG00000101421 CHMP4B epididymis glandular cells Low Enhanced Q9H444 +ENSG00000101421 CHMP4B prostate glandular cells Medium Enhanced Q9H444 +ENSG00000101421 CHMP4B seminal vesicle glandular cells Low Enhanced Q9H444 +ENSG00000101421 CHMP4B testis cells in seminiferous ducts Medium Enhanced Q9H444 +ENSG00000101421 CHMP4B testis Leydig cells Medium Enhanced Q9H444 +ENSG00000101439 CST3 epididymis glandular cells High Enhanced P01034 +ENSG00000101439 CST3 prostate glandular cells High Enhanced P01034 +ENSG00000101439 CST3 seminal vesicle glandular cells Medium Enhanced P01034 +ENSG00000101439 CST3 testis cells in seminiferous ducts Medium Enhanced P01034 +ENSG00000101439 CST3 testis Leydig cells Medium Enhanced P01034 +ENSG00000101443 WFDC2 epididymis glandular cells High Enhanced Q14508 +ENSG00000101443 WFDC2 prostate glandular cells High Enhanced Q14508 +ENSG00000101443 WFDC2 seminal vesicle glandular cells High Enhanced Q14508 +ENSG00000101443 WFDC2 testis Leydig cells Low Enhanced Q14508 +ENSG00000101446 SPINT3 epididymis glandular cells High Enhanced P49223 +ENSG00000101460 MAP1LC3A testis Leydig cells Low Enhanced Q9H492 +ENSG00000101577 LPIN2 epididymis glandular cells Low Enhanced Q92539 +ENSG00000101577 LPIN2 prostate glandular cells Low Enhanced Q92539 +ENSG00000101577 LPIN2 seminal vesicle glandular cells Low Enhanced Q92539 +ENSG00000101577 LPIN2 testis cells in seminiferous ducts Medium Enhanced Q92539 +ENSG00000101577 LPIN2 testis Leydig cells Low Enhanced Q92539 +ENSG00000101680 LAMA1 epididymis glandular cells Low Enhanced P25391 +ENSG00000101680 LAMA1 prostate glandular cells Low Enhanced P25391 +ENSG00000101680 LAMA1 testis cells in seminiferous ducts Medium Enhanced P25391 +ENSG00000101751 POLI epididymis glandular cells Medium Enhanced Q9UNA4 +ENSG00000101751 POLI prostate glandular cells Low Enhanced Q9UNA4 +ENSG00000101751 POLI seminal vesicle glandular cells Medium Enhanced Q9UNA4 +ENSG00000101751 POLI testis cells in seminiferous ducts High Enhanced Q9UNA4 +ENSG00000101751 POLI testis Leydig cells Low Enhanced Q9UNA4 +ENSG00000101811 CSTF2 epididymis glandular cells Medium Enhanced P33240 +ENSG00000101811 CSTF2 prostate glandular cells Medium Enhanced P33240 +ENSG00000101811 CSTF2 seminal vesicle glandular cells Medium Enhanced P33240 +ENSG00000101811 CSTF2 testis cells in seminiferous ducts Medium Enhanced P33240 +ENSG00000101811 CSTF2 testis Leydig cells Medium Enhanced P33240 +ENSG00000101842 VSIG1 epididymis glandular cells Low Enhanced Q86XK7 +ENSG00000101842 VSIG1 testis elongated or late spermatids High Enhanced Q86XK7 +ENSG00000101842 VSIG1 testis pachytene spermatocytes High Enhanced Q86XK7 +ENSG00000101842 VSIG1 testis preleptotene spermatocytes High Enhanced Q86XK7 +ENSG00000101842 VSIG1 testis round or early spermatids High Enhanced Q86XK7 +ENSG00000101842 VSIG1 testis spermatogonia High Enhanced Q86XK7 +ENSG00000101846 STS epididymis glandular cells Low Enhanced P08842 +ENSG00000101846 STS prostate glandular cells Low Enhanced P08842 +ENSG00000101846 STS seminal vesicle glandular cells Low Enhanced P08842 +ENSG00000101846 STS testis cells in seminiferous ducts Low Enhanced P08842 +ENSG00000101846 STS testis Leydig cells Low Enhanced P08842 +ENSG00000101850 GPR143 epididymis glandular cells Low Enhanced P51810 +ENSG00000101850 GPR143 prostate glandular cells Low Enhanced P51810 +ENSG00000101850 GPR143 seminal vesicle glandular cells Low Enhanced P51810 +ENSG00000101850 GPR143 testis cells in seminiferous ducts Low Enhanced P51810 +ENSG00000101850 GPR143 testis Leydig cells Low Enhanced P51810 +ENSG00000101856 PGRMC1 epididymis glandular cells Medium Enhanced O00264 +ENSG00000101856 PGRMC1 prostate glandular cells Medium Enhanced O00264 +ENSG00000101856 PGRMC1 seminal vesicle glandular cells High Enhanced O00264 +ENSG00000101856 PGRMC1 testis cells in seminiferous ducts Low Enhanced O00264 +ENSG00000101856 PGRMC1 testis Leydig cells High Enhanced O00264 +ENSG00000101868 POLA1 epididymis glandular cells Medium Enhanced P09884 +ENSG00000101868 POLA1 prostate glandular cells Low Enhanced P09884 +ENSG00000101868 POLA1 seminal vesicle glandular cells Low Enhanced P09884 +ENSG00000101868 POLA1 testis cells in seminiferous ducts Medium Enhanced P09884 +ENSG00000101868 POLA1 testis Leydig cells Low Enhanced P09884 +ENSG00000101882 NKAP epididymis glandular cells High Supported Q8N5F7 +ENSG00000101882 NKAP prostate glandular cells Medium Supported Q8N5F7 +ENSG00000101882 NKAP seminal vesicle glandular cells Medium Supported Q8N5F7 +ENSG00000101882 NKAP testis cells in seminiferous ducts High Supported Q8N5F7 +ENSG00000101882 NKAP testis Leydig cells Medium Supported Q8N5F7 +ENSG00000101911 PRPS2 seminal vesicle glandular cells High Enhanced P11908 +ENSG00000101911 PRPS2 testis cells in seminiferous ducts Medium Enhanced P11908 +ENSG00000101911 PRPS2 testis Leydig cells High Enhanced P11908 +ENSG00000101940 WDR13 epididymis glandular cells Medium Enhanced Q9H1Z4 +ENSG00000101940 WDR13 prostate glandular cells Medium Enhanced Q9H1Z4 +ENSG00000101940 WDR13 seminal vesicle glandular cells Medium Enhanced Q9H1Z4 +ENSG00000101940 WDR13 testis cells in seminiferous ducts Medium Enhanced Q9H1Z4 +ENSG00000101940 WDR13 testis Leydig cells Medium Enhanced Q9H1Z4 +ENSG00000101972 STAG2 epididymis glandular cells High Supported Q8N3U4 +ENSG00000101972 STAG2 prostate glandular cells Medium Supported Q8N3U4 +ENSG00000101972 STAG2 seminal vesicle glandular cells Medium Supported Q8N3U4 +ENSG00000101972 STAG2 testis Leydig cells Medium Supported Q8N3U4 +ENSG00000102010 BMX epididymis glandular cells High Enhanced P51813 +ENSG00000102021 LUZP4 testis elongated or late spermatids Low Enhanced Q9P127 +ENSG00000102021 LUZP4 testis Leydig cells Low Enhanced Q9P127 +ENSG00000102021 LUZP4 testis pachytene spermatocytes Low Enhanced Q9P127 +ENSG00000102021 LUZP4 testis preleptotene spermatocytes High Enhanced Q9P127 +ENSG00000102021 LUZP4 testis round or early spermatids Low Enhanced Q9P127 +ENSG00000102021 LUZP4 testis spermatogonia Medium Enhanced Q9P127 +ENSG00000102024 PLS3 epididymis glandular cells High Enhanced P13797 +ENSG00000102024 PLS3 prostate glandular cells Low Enhanced P13797 +ENSG00000102024 PLS3 seminal vesicle glandular cells High Enhanced P13797 +ENSG00000102024 PLS3 testis cells in seminiferous ducts Medium Enhanced P13797 +ENSG00000102024 PLS3 testis Leydig cells High Enhanced P13797 +ENSG00000102030 NAA10 epididymis glandular cells Medium Supported P41227 +ENSG00000102030 NAA10 prostate glandular cells Medium Supported P41227 +ENSG00000102030 NAA10 seminal vesicle glandular cells Medium Supported P41227 +ENSG00000102030 NAA10 testis cells in seminiferous ducts High Supported P41227 +ENSG00000102030 NAA10 testis Leydig cells Low Supported P41227 +ENSG00000102034 ELF4 epididymis glandular cells Medium Enhanced Q99607 +ENSG00000102034 ELF4 prostate glandular cells Medium Enhanced Q99607 +ENSG00000102034 ELF4 seminal vesicle glandular cells Medium Enhanced Q99607 +ENSG00000102034 ELF4 testis cells in seminiferous ducts Low Enhanced Q99607 +ENSG00000102034 ELF4 testis Leydig cells Medium Enhanced Q99607 +ENSG00000102048 ASB9 testis elongated or late spermatids Low Enhanced Q96DX5 +ENSG00000102048 ASB9 testis Leydig cells Low Enhanced Q96DX5 +ENSG00000102048 ASB9 testis pachytene spermatocytes Low Enhanced Q96DX5 +ENSG00000102048 ASB9 testis preleptotene spermatocytes High Enhanced Q96DX5 +ENSG00000102048 ASB9 testis round or early spermatids Low Enhanced Q96DX5 +ENSG00000102048 ASB9 testis spermatogonia High Enhanced Q96DX5 +ENSG00000102054 RBBP7 epididymis glandular cells High Supported Q16576 +ENSG00000102054 RBBP7 prostate glandular cells High Supported Q16576 +ENSG00000102054 RBBP7 seminal vesicle glandular cells High Supported Q16576 +ENSG00000102054 RBBP7 testis cells in seminiferous ducts High Supported Q16576 +ENSG00000102054 RBBP7 testis Leydig cells High Supported Q16576 +ENSG00000102098 SCML2 testis Leydig cells Low Enhanced Q9UQR0 +ENSG00000102098 SCML2 testis pachytene spermatocytes Medium Enhanced Q9UQR0 +ENSG00000102098 SCML2 testis preleptotene spermatocytes High Enhanced Q9UQR0 +ENSG00000102098 SCML2 testis round or early spermatids Low Enhanced Q9UQR0 +ENSG00000102098 SCML2 testis spermatogonia High Enhanced Q9UQR0 +ENSG00000102103 PQBP1 epididymis glandular cells High Supported O60828 +ENSG00000102103 PQBP1 prostate glandular cells High Supported O60828 +ENSG00000102103 PQBP1 seminal vesicle glandular cells High Supported O60828 +ENSG00000102103 PQBP1 testis cells in seminiferous ducts High Supported O60828 +ENSG00000102103 PQBP1 testis Leydig cells Medium Supported O60828 +ENSG00000102119 EMD epididymis glandular cells Medium Enhanced P50402 +ENSG00000102119 EMD prostate glandular cells Medium Enhanced P50402 +ENSG00000102119 EMD seminal vesicle glandular cells Medium Enhanced P50402 +ENSG00000102119 EMD testis cells in seminiferous ducts Medium Enhanced P50402 +ENSG00000102119 EMD testis Leydig cells Low Enhanced P50402 +ENSG00000102181 CD99L2 epididymis glandular cells Medium Enhanced Q8TCZ2 +ENSG00000102181 CD99L2 seminal vesicle glandular cells Medium Enhanced Q8TCZ2 +ENSG00000102181 CD99L2 testis cells in seminiferous ducts Medium Enhanced Q8TCZ2 +ENSG00000102181 CD99L2 testis Leydig cells Low Enhanced Q8TCZ2 +ENSG00000102189 EEA1 epididymis glandular cells Low Enhanced Q15075 +ENSG00000102189 EEA1 prostate glandular cells Medium Enhanced Q15075 +ENSG00000102189 EEA1 seminal vesicle glandular cells Low Enhanced Q15075 +ENSG00000102189 EEA1 testis cells in seminiferous ducts Medium Enhanced Q15075 +ENSG00000102189 EEA1 testis Leydig cells Medium Enhanced Q15075 +ENSG00000102226 USP11 epididymis glandular cells Low Enhanced P51784 +ENSG00000102226 USP11 seminal vesicle glandular cells Low Enhanced P51784 +ENSG00000102226 USP11 testis cells in seminiferous ducts Medium Enhanced P51784 +ENSG00000102226 USP11 testis Leydig cells Low Enhanced P51784 +ENSG00000102241 HTATSF1 epididymis glandular cells High Supported O43719 +ENSG00000102241 HTATSF1 prostate glandular cells High Supported O43719 +ENSG00000102241 HTATSF1 seminal vesicle glandular cells High Supported O43719 +ENSG00000102241 HTATSF1 testis cells in seminiferous ducts High Supported O43719 +ENSG00000102241 HTATSF1 testis Leydig cells High Supported O43719 +ENSG00000102312 PORCN seminal vesicle glandular cells Low Enhanced Q9H237 +ENSG00000102312 PORCN testis cells in seminiferous ducts Medium Enhanced Q9H237 +ENSG00000102312 PORCN testis Leydig cells Low Enhanced Q9H237 +ENSG00000102316 MAGED2 epididymis glandular cells High Supported Q9UNF1 +ENSG00000102316 MAGED2 prostate glandular cells High Supported Q9UNF1 +ENSG00000102316 MAGED2 seminal vesicle glandular cells High Supported Q9UNF1 +ENSG00000102316 MAGED2 testis cells in seminiferous ducts High Supported Q9UNF1 +ENSG00000102316 MAGED2 testis Leydig cells Medium Supported Q9UNF1 +ENSG00000102317 RBM3 epididymis glandular cells Medium Enhanced P98179 +ENSG00000102317 RBM3 testis cells in seminiferous ducts Medium Enhanced P98179 +ENSG00000102317 RBM3 testis Leydig cells Medium Enhanced P98179 +ENSG00000102393 GLA epididymis glandular cells High Enhanced P06280 +ENSG00000102393 GLA prostate glandular cells Medium Enhanced P06280 +ENSG00000102393 GLA seminal vesicle glandular cells High Enhanced P06280 +ENSG00000102393 GLA testis Leydig cells Medium Enhanced P06280 +ENSG00000102524 TNFSF13B epididymis glandular cells Medium Enhanced Q9Y275 +ENSG00000102524 TNFSF13B prostate glandular cells Medium Enhanced Q9Y275 +ENSG00000102524 TNFSF13B seminal vesicle glandular cells Medium Enhanced Q9Y275 +ENSG00000102524 TNFSF13B testis cells in seminiferous ducts High Enhanced Q9Y275 +ENSG00000102524 TNFSF13B testis Leydig cells Medium Enhanced Q9Y275 +ENSG00000102572 STK24 epididymis glandular cells Medium Enhanced Q9Y6E0 +ENSG00000102572 STK24 prostate glandular cells High Enhanced Q9Y6E0 +ENSG00000102572 STK24 seminal vesicle glandular cells Medium Enhanced Q9Y6E0 +ENSG00000102572 STK24 testis cells in seminiferous ducts Medium Enhanced Q9Y6E0 +ENSG00000102572 STK24 testis Leydig cells Medium Enhanced Q9Y6E0 +ENSG00000102678 FGF9 testis Leydig cells Low Enhanced P31371 +ENSG00000102786 INTS6 epididymis glandular cells Medium Supported Q9UL03 +ENSG00000102786 INTS6 prostate glandular cells Low Supported Q9UL03 +ENSG00000102786 INTS6 seminal vesicle glandular cells Medium Supported Q9UL03 +ENSG00000102786 INTS6 testis cells in seminiferous ducts Medium Supported Q9UL03 +ENSG00000102786 INTS6 testis Leydig cells Low Supported Q9UL03 +ENSG00000102837 OLFM4 epididymis glandular cells Medium Enhanced Q6UX06 +ENSG00000102871 TRADD epididymis glandular cells Medium Enhanced Q15628 +ENSG00000102871 TRADD prostate glandular cells Low Enhanced Q15628 +ENSG00000102871 TRADD seminal vesicle glandular cells Medium Enhanced Q15628 +ENSG00000102871 TRADD testis cells in seminiferous ducts Medium Enhanced Q15628 +ENSG00000102871 TRADD testis Leydig cells Medium Enhanced Q15628 +ENSG00000102898 NUTF2 epididymis glandular cells High Enhanced P61970 +ENSG00000102898 NUTF2 seminal vesicle glandular cells Low Enhanced P61970 +ENSG00000102898 NUTF2 testis cells in seminiferous ducts Medium Enhanced P61970 +ENSG00000102898 NUTF2 testis Leydig cells Low Enhanced P61970 +ENSG00000102934 PLLP seminal vesicle glandular cells Medium Enhanced Q9Y342 +ENSG00000102974 CTCF epididymis glandular cells High Supported P49711 +ENSG00000102974 CTCF prostate glandular cells Medium Supported P49711 +ENSG00000102974 CTCF seminal vesicle glandular cells Medium Supported P49711 +ENSG00000102974 CTCF testis cells in seminiferous ducts Medium Supported P49711 +ENSG00000102974 CTCF testis Leydig cells High Supported P49711 +ENSG00000102978 POLR2C epididymis glandular cells Medium Enhanced P19387 +ENSG00000102978 POLR2C prostate glandular cells Low Enhanced P19387 +ENSG00000102978 POLR2C seminal vesicle glandular cells Medium Enhanced P19387 +ENSG00000102978 POLR2C testis cells in seminiferous ducts High Enhanced P19387 +ENSG00000102978 POLR2C testis Leydig cells Medium Enhanced P19387 +ENSG00000102984 ZNF821 testis Leydig cells High Enhanced O75541 +ENSG00000102984 ZNF821 testis peritubular cells Low Enhanced O75541 +ENSG00000102984 ZNF821 testis sertoli cells High Enhanced O75541 +ENSG00000103023 PRSS54 testis cells in seminiferous ducts Medium Enhanced Q6PEW0 +ENSG00000103034 NDRG4 testis cells in seminiferous ducts Low Enhanced Q9ULP0 +ENSG00000103035 PSMD7 epididymis glandular cells Medium Enhanced P51665 +ENSG00000103035 PSMD7 prostate glandular cells Medium Enhanced P51665 +ENSG00000103035 PSMD7 seminal vesicle glandular cells Low Enhanced P51665 +ENSG00000103035 PSMD7 testis cells in seminiferous ducts High Enhanced P51665 +ENSG00000103035 PSMD7 testis Leydig cells High Enhanced P51665 +ENSG00000103044 HAS3 testis cells in seminiferous ducts Low Supported O00219 +ENSG00000103044 HAS3 testis Leydig cells Medium Supported O00219 +ENSG00000103066 PLA2G15 epididymis glandular cells High Enhanced Q8NCC3 +ENSG00000103066 PLA2G15 prostate glandular cells Medium Enhanced Q8NCC3 +ENSG00000103066 PLA2G15 testis cells in seminiferous ducts Medium Enhanced Q8NCC3 +ENSG00000103066 PLA2G15 testis Leydig cells Medium Enhanced Q8NCC3 +ENSG00000103150 MLYCD epididymis glandular cells Medium Enhanced O95822 +ENSG00000103150 MLYCD prostate glandular cells Medium Enhanced O95822 +ENSG00000103150 MLYCD seminal vesicle glandular cells Medium Enhanced O95822 +ENSG00000103150 MLYCD testis cells in seminiferous ducts High Enhanced O95822 +ENSG00000103150 MLYCD testis Leydig cells Medium Enhanced O95822 +ENSG00000103187 COTL1 seminal vesicle glandular cells Low Enhanced Q14019 +ENSG00000103194 USP10 epididymis glandular cells High Enhanced Q14694 +ENSG00000103194 USP10 prostate glandular cells High Enhanced Q14694 +ENSG00000103194 USP10 seminal vesicle glandular cells High Enhanced Q14694 +ENSG00000103194 USP10 testis cells in seminiferous ducts High Enhanced Q14694 +ENSG00000103194 USP10 testis Leydig cells High Enhanced Q14694 +ENSG00000103199 ZNF500 epididymis glandular cells Medium Supported O60304 +ENSG00000103199 ZNF500 prostate glandular cells Medium Supported O60304 +ENSG00000103199 ZNF500 seminal vesicle glandular cells Medium Supported O60304 +ENSG00000103199 ZNF500 testis cells in seminiferous ducts High Supported O60304 +ENSG00000103199 ZNF500 testis Leydig cells High Supported O60304 +ENSG00000103249 CLCN7 epididymis glandular cells Medium Supported P51798 +ENSG00000103249 CLCN7 prostate glandular cells High Supported P51798 +ENSG00000103249 CLCN7 seminal vesicle glandular cells Medium Supported P51798 +ENSG00000103249 CLCN7 testis cells in seminiferous ducts Medium Supported P51798 +ENSG00000103249 CLCN7 testis Leydig cells Medium Supported P51798 +ENSG00000103254 FAM173A epididymis glandular cells High Enhanced Q9BQD7 +ENSG00000103254 FAM173A prostate glandular cells Medium Enhanced Q9BQD7 +ENSG00000103254 FAM173A seminal vesicle glandular cells Medium Enhanced Q9BQD7 +ENSG00000103254 FAM173A testis cells in seminiferous ducts Medium Enhanced Q9BQD7 +ENSG00000103254 FAM173A testis Leydig cells Medium Enhanced Q9BQD7 +ENSG00000103266 STUB1 epididymis glandular cells High Enhanced Q9UNE7 +ENSG00000103266 STUB1 prostate glandular cells Medium Enhanced Q9UNE7 +ENSG00000103266 STUB1 seminal vesicle glandular cells Medium Enhanced Q9UNE7 +ENSG00000103266 STUB1 testis Leydig cells Low Enhanced Q9UNE7 +ENSG00000103274 NUBP1 epididymis glandular cells Medium Enhanced P53384 +ENSG00000103274 NUBP1 prostate glandular cells Low Enhanced P53384 +ENSG00000103274 NUBP1 seminal vesicle glandular cells Medium Enhanced P53384 +ENSG00000103274 NUBP1 testis cells in seminiferous ducts Medium Enhanced P53384 +ENSG00000103274 NUBP1 testis Leydig cells Medium Enhanced P53384 +ENSG00000103316 CRYM epididymis glandular cells Low Enhanced I3NI53 +ENSG00000103316 CRYM prostate glandular cells High Enhanced I3NI53 +ENSG00000103316 CRYM testis cells in seminiferous ducts Low Enhanced I3NI53 +ENSG00000103415 HMOX2 epididymis glandular cells Medium Supported NA +ENSG00000103415 HMOX2 prostate glandular cells Medium Supported NA +ENSG00000103415 HMOX2 seminal vesicle glandular cells Medium Supported NA +ENSG00000103415 HMOX2 testis cells in seminiferous ducts High Supported NA +ENSG00000103415 HMOX2 testis Leydig cells High Supported NA +ENSG00000103460 TOX3 epididymis glandular cells Medium Enhanced O15405 +ENSG00000103460 TOX3 prostate glandular cells Low Enhanced O15405 +ENSG00000103460 TOX3 testis Leydig cells Low Enhanced O15405 +ENSG00000103479 RBL2 epididymis glandular cells High Supported Q08999 +ENSG00000103479 RBL2 prostate glandular cells High Supported Q08999 +ENSG00000103479 RBL2 seminal vesicle glandular cells High Supported Q08999 +ENSG00000103479 RBL2 testis cells in seminiferous ducts High Supported Q08999 +ENSG00000103479 RBL2 testis Leydig cells Medium Supported Q08999 +ENSG00000103490 PYCARD epididymis glandular cells Low Enhanced Q9ULZ3 +ENSG00000103490 PYCARD prostate glandular cells Medium Enhanced Q9ULZ3 +ENSG00000103490 PYCARD seminal vesicle glandular cells Low Enhanced Q9ULZ3 +ENSG00000103507 BCKDK epididymis glandular cells Medium Supported O14874 +ENSG00000103507 BCKDK prostate glandular cells Low Supported O14874 +ENSG00000103507 BCKDK seminal vesicle glandular cells Medium Supported O14874 +ENSG00000103507 BCKDK testis cells in seminiferous ducts Medium Supported O14874 +ENSG00000103507 BCKDK testis Leydig cells High Supported O14874 +ENSG00000103534 TMC5 epididymis glandular cells Medium Enhanced Q6UXY8 +ENSG00000103534 TMC5 prostate glandular cells Medium Enhanced Q6UXY8 +ENSG00000103534 TMC5 seminal vesicle glandular cells Medium Enhanced Q6UXY8 +ENSG00000103534 TMC5 testis cells in seminiferous ducts Medium Enhanced Q6UXY8 +ENSG00000103534 TMC5 testis Leydig cells Medium Enhanced Q6UXY8 +ENSG00000103546 SLC6A2 testis cells in seminiferous ducts Medium Enhanced P23975 +ENSG00000103546 SLC6A2 testis Leydig cells Medium Enhanced P23975 +ENSG00000103591 AAGAB epididymis glandular cells Medium Supported Q6PD74 +ENSG00000103591 AAGAB prostate glandular cells High Supported Q6PD74 +ENSG00000103591 AAGAB seminal vesicle glandular cells High Supported Q6PD74 +ENSG00000103591 AAGAB testis cells in seminiferous ducts High Supported Q6PD74 +ENSG00000103591 AAGAB testis Leydig cells High Supported Q6PD74 +ENSG00000103642 LACTB epididymis glandular cells Medium Enhanced P83111 +ENSG00000103642 LACTB prostate glandular cells Medium Enhanced P83111 +ENSG00000103642 LACTB seminal vesicle glandular cells Medium Enhanced P83111 +ENSG00000103642 LACTB testis cells in seminiferous ducts Low Enhanced P83111 +ENSG00000103642 LACTB testis Leydig cells Medium Enhanced P83111 +ENSG00000103647 CORO2B epididymis glandular cells Low Enhanced Q9UQ03 +ENSG00000103647 CORO2B testis cells in seminiferous ducts Low Enhanced Q9UQ03 +ENSG00000103647 CORO2B testis Leydig cells Low Enhanced Q9UQ03 +ENSG00000103811 CTSH epididymis glandular cells Low Enhanced P09668 +ENSG00000103811 CTSH prostate glandular cells Medium Enhanced P09668 +ENSG00000103811 CTSH seminal vesicle glandular cells Low Enhanced P09668 +ENSG00000103811 CTSH testis Leydig cells Low Enhanced P09668 +ENSG00000103855 CD276 epididymis glandular cells Medium Enhanced Q5ZPR3 +ENSG00000103855 CD276 prostate glandular cells High Enhanced Q5ZPR3 +ENSG00000103855 CD276 seminal vesicle glandular cells Medium Enhanced Q5ZPR3 +ENSG00000103855 CD276 testis cells in seminiferous ducts Low Enhanced Q5ZPR3 +ENSG00000103855 CD276 testis Leydig cells Medium Enhanced Q5ZPR3 +ENSG00000103876 FAH epididymis glandular cells Low Enhanced P16930 +ENSG00000103876 FAH seminal vesicle glandular cells Low Enhanced P16930 +ENSG00000103876 FAH testis cells in seminiferous ducts Low Enhanced P16930 +ENSG00000103876 FAH testis Leydig cells Low Enhanced P16930 +ENSG00000103978 TMEM87A epididymis glandular cells High Enhanced Q8NBN3 +ENSG00000103978 TMEM87A prostate glandular cells High Enhanced Q8NBN3 +ENSG00000103978 TMEM87A seminal vesicle glandular cells Medium Enhanced Q8NBN3 +ENSG00000103978 TMEM87A testis cells in seminiferous ducts Medium Enhanced Q8NBN3 +ENSG00000103978 TMEM87A testis Leydig cells Medium Enhanced Q8NBN3 +ENSG00000104064 GABPB1 epididymis glandular cells High Supported Q06547 +ENSG00000104064 GABPB1 prostate glandular cells High Supported Q06547 +ENSG00000104064 GABPB1 seminal vesicle glandular cells High Supported Q06547 +ENSG00000104064 GABPB1 testis cells in seminiferous ducts High Supported Q06547 +ENSG00000104064 GABPB1 testis Leydig cells High Supported Q06547 +ENSG00000104067 TJP1 epididymis glandular cells Medium Enhanced G3V1L9 +ENSG00000104067 TJP1 prostate glandular cells Low Enhanced G3V1L9 +ENSG00000104067 TJP1 seminal vesicle glandular cells Low Enhanced G3V1L9 +ENSG00000104067 TJP1 testis cells in seminiferous ducts Medium Enhanced G3V1L9 +ENSG00000104067 TJP1 testis Leydig cells Low Enhanced G3V1L9 +ENSG00000104140 RHOV prostate glandular cells Low Enhanced Q96L33 +ENSG00000104147 OIP5 testis cells in seminiferous ducts High Enhanced O43482 +ENSG00000104177 MYEF2 epididymis glandular cells High Supported Q9P2K5 +ENSG00000104177 MYEF2 prostate glandular cells High Supported Q9P2K5 +ENSG00000104177 MYEF2 seminal vesicle glandular cells High Supported Q9P2K5 +ENSG00000104177 MYEF2 testis Leydig cells Medium Supported Q9P2K5 +ENSG00000104177 MYEF2 testis pachytene spermatocytes High Supported Q9P2K5 +ENSG00000104177 MYEF2 testis preleptotene spermatocytes High Supported Q9P2K5 +ENSG00000104177 MYEF2 testis round or early spermatids High Supported Q9P2K5 +ENSG00000104177 MYEF2 testis sertoli cells High Supported Q9P2K5 +ENSG00000104177 MYEF2 testis spermatogonia High Supported Q9P2K5 +ENSG00000104205 SGK3 epididymis glandular cells Medium Supported Q96BR1 +ENSG00000104205 SGK3 prostate glandular cells Medium Supported Q96BR1 +ENSG00000104205 SGK3 seminal vesicle glandular cells Medium Supported Q96BR1 +ENSG00000104205 SGK3 testis cells in seminiferous ducts Medium Supported Q96BR1 +ENSG00000104205 SGK3 testis Leydig cells High Supported Q96BR1 +ENSG00000104221 BRF2 epididymis glandular cells Medium Enhanced Q9HAW0 +ENSG00000104221 BRF2 prostate glandular cells Medium Enhanced Q9HAW0 +ENSG00000104221 BRF2 seminal vesicle glandular cells Medium Enhanced Q9HAW0 +ENSG00000104221 BRF2 testis cells in seminiferous ducts High Enhanced Q9HAW0 +ENSG00000104221 BRF2 testis Leydig cells Medium Enhanced Q9HAW0 +ENSG00000104267 CA2 seminal vesicle glandular cells High Enhanced P00918 +ENSG00000104320 NBN epididymis glandular cells Medium Supported O60934 +ENSG00000104320 NBN prostate glandular cells Low Supported O60934 +ENSG00000104320 NBN seminal vesicle glandular cells Medium Supported O60934 +ENSG00000104320 NBN testis cells in seminiferous ducts Medium Supported O60934 +ENSG00000104320 NBN testis Leydig cells Low Supported O60934 +ENSG00000104324 CPQ epididymis glandular cells Low Enhanced Q9Y646 +ENSG00000104324 CPQ prostate glandular cells Low Enhanced Q9Y646 +ENSG00000104324 CPQ seminal vesicle glandular cells Low Enhanced Q9Y646 +ENSG00000104324 CPQ testis Leydig cells Low Enhanced Q9Y646 +ENSG00000104325 DECR1 epididymis glandular cells Medium Enhanced Q16698 +ENSG00000104325 DECR1 prostate glandular cells Medium Enhanced Q16698 +ENSG00000104325 DECR1 seminal vesicle glandular cells Medium Enhanced Q16698 +ENSG00000104325 DECR1 testis cells in seminiferous ducts Medium Enhanced Q16698 +ENSG00000104325 DECR1 testis Leydig cells High Enhanced Q16698 +ENSG00000104331 IMPAD1 epididymis glandular cells Low Supported Q9NX62 +ENSG00000104331 IMPAD1 prostate glandular cells High Supported Q9NX62 +ENSG00000104331 IMPAD1 seminal vesicle glandular cells High Supported Q9NX62 +ENSG00000104331 IMPAD1 testis cells in seminiferous ducts Medium Supported Q9NX62 +ENSG00000104331 IMPAD1 testis Leydig cells High Supported Q9NX62 +ENSG00000104365 IKBKB epididymis glandular cells Medium Enhanced O14920 +ENSG00000104365 IKBKB prostate glandular cells Low Enhanced O14920 +ENSG00000104365 IKBKB seminal vesicle glandular cells Low Enhanced O14920 +ENSG00000104365 IKBKB testis cells in seminiferous ducts Medium Enhanced O14920 +ENSG00000104365 IKBKB testis Leydig cells Low Enhanced O14920 +ENSG00000104381 GDAP1 seminal vesicle glandular cells Low Enhanced Q8TB36 +ENSG00000104381 GDAP1 testis cells in seminiferous ducts Low Enhanced Q8TB36 +ENSG00000104381 GDAP1 testis Leydig cells Low Enhanced Q8TB36 +ENSG00000104413 ESRP1 epididymis glandular cells Medium Enhanced Q6NXG1 +ENSG00000104413 ESRP1 prostate glandular cells Low Enhanced Q6NXG1 +ENSG00000104413 ESRP1 seminal vesicle glandular cells Medium Enhanced Q6NXG1 +ENSG00000104413 ESRP1 testis cells in seminiferous ducts Medium Enhanced Q6NXG1 +ENSG00000104413 ESRP1 testis Leydig cells Low Enhanced Q6NXG1 +ENSG00000104447 TRPS1 epididymis glandular cells Low Enhanced Q9UHF7 +ENSG00000104447 TRPS1 prostate glandular cells Low Enhanced Q9UHF7 +ENSG00000104447 TRPS1 testis cells in seminiferous ducts Medium Enhanced Q9UHF7 +ENSG00000104447 TRPS1 testis Leydig cells Low Enhanced Q9UHF7 +ENSG00000104450 SPAG1 testis pachytene spermatocytes High Enhanced Q07617 +ENSG00000104450 SPAG1 testis round or early spermatids High Enhanced Q07617 +ENSG00000104529 EEF1D epididymis glandular cells High Supported E9PMW7 +ENSG00000104529 EEF1D prostate glandular cells Medium Supported E9PMW7 +ENSG00000104529 EEF1D seminal vesicle glandular cells High Supported E9PMW7 +ENSG00000104529 EEF1D testis cells in seminiferous ducts Medium Supported E9PMW7 +ENSG00000104529 EEF1D testis Leydig cells Low Supported E9PMW7 +ENSG00000104549 SQLE epididymis glandular cells Medium Enhanced Q14534 +ENSG00000104549 SQLE prostate glandular cells Low Enhanced Q14534 +ENSG00000104549 SQLE testis Leydig cells High Enhanced Q14534 +ENSG00000104611 SH2D4A epididymis glandular cells Low Enhanced Q9H788 +ENSG00000104611 SH2D4A prostate glandular cells Low Enhanced Q9H788 +ENSG00000104611 SH2D4A seminal vesicle glandular cells Medium Enhanced Q9H788 +ENSG00000104611 SH2D4A testis cells in seminiferous ducts Low Enhanced Q9H788 +ENSG00000104611 SH2D4A testis Leydig cells Medium Enhanced Q9H788 +ENSG00000104738 MCM4 epididymis glandular cells Medium Supported P33991 +ENSG00000104738 MCM4 prostate glandular cells Medium Supported P33991 +ENSG00000104738 MCM4 seminal vesicle glandular cells High Supported P33991 +ENSG00000104738 MCM4 testis cells in seminiferous ducts High Supported P33991 +ENSG00000104738 MCM4 testis Leydig cells Medium Supported P33991 +ENSG00000104755 ADAM2 testis elongated or late spermatids Medium Enhanced NA +ENSG00000104755 ADAM2 testis Leydig cells Low Enhanced NA +ENSG00000104755 ADAM2 testis pachytene spermatocytes Medium Enhanced NA +ENSG00000104755 ADAM2 testis preleptotene spermatocytes Low Enhanced NA +ENSG00000104755 ADAM2 testis round or early spermatids High Enhanced NA +ENSG00000104763 ASAH1 epididymis glandular cells High Supported Q13510 +ENSG00000104763 ASAH1 prostate glandular cells High Supported Q13510 +ENSG00000104763 ASAH1 seminal vesicle glandular cells High Supported Q13510 +ENSG00000104763 ASAH1 testis cells in seminiferous ducts Medium Supported Q13510 +ENSG00000104763 ASAH1 testis Leydig cells High Supported Q13510 +ENSG00000104765 BNIP3L epididymis glandular cells High Enhanced O60238 +ENSG00000104765 BNIP3L prostate glandular cells High Enhanced O60238 +ENSG00000104765 BNIP3L seminal vesicle glandular cells High Enhanced O60238 +ENSG00000104765 BNIP3L testis cells in seminiferous ducts High Enhanced O60238 +ENSG00000104765 BNIP3L testis Leydig cells High Enhanced O60238 +ENSG00000104774 MAN2B1 epididymis glandular cells High Supported O00754 +ENSG00000104774 MAN2B1 prostate glandular cells High Supported O00754 +ENSG00000104774 MAN2B1 seminal vesicle glandular cells Medium Supported O00754 +ENSG00000104774 MAN2B1 testis cells in seminiferous ducts High Supported O00754 +ENSG00000104774 MAN2B1 testis Leydig cells Medium Supported O00754 +ENSG00000104805 NUCB1 epididymis glandular cells High Enhanced Q02818 +ENSG00000104805 NUCB1 prostate glandular cells High Enhanced Q02818 +ENSG00000104805 NUCB1 seminal vesicle glandular cells Low Enhanced Q02818 +ENSG00000104805 NUCB1 testis Leydig cells Low Enhanced Q02818 +ENSG00000104812 GYS1 epididymis glandular cells Medium Enhanced P13807 +ENSG00000104812 GYS1 prostate glandular cells High Enhanced P13807 +ENSG00000104812 GYS1 seminal vesicle glandular cells High Enhanced P13807 +ENSG00000104812 GYS1 testis cells in seminiferous ducts Medium Enhanced P13807 +ENSG00000104812 GYS1 testis Leydig cells Medium Enhanced P13807 +ENSG00000104823 ECH1 epididymis glandular cells High Supported M0QZX8 +ENSG00000104823 ECH1 prostate glandular cells High Supported M0QZX8 +ENSG00000104823 ECH1 seminal vesicle glandular cells Medium Supported M0QZX8 +ENSG00000104823 ECH1 testis cells in seminiferous ducts Medium Supported M0QZX8 +ENSG00000104823 ECH1 testis Leydig cells High Supported M0QZX8 +ENSG00000104824 HNRNPL epididymis glandular cells High Supported B4DVF8 +ENSG00000104824 HNRNPL prostate glandular cells High Supported B4DVF8 +ENSG00000104824 HNRNPL seminal vesicle glandular cells High Supported B4DVF8 +ENSG00000104824 HNRNPL testis cells in seminiferous ducts High Supported B4DVF8 +ENSG00000104824 HNRNPL testis Leydig cells High Supported B4DVF8 +ENSG00000104852 SNRNP70 epididymis glandular cells High Supported P08621 +ENSG00000104852 SNRNP70 prostate glandular cells High Supported P08621 +ENSG00000104852 SNRNP70 seminal vesicle glandular cells High Supported P08621 +ENSG00000104852 SNRNP70 testis cells in seminiferous ducts High Supported P08621 +ENSG00000104852 SNRNP70 testis Leydig cells High Supported P08621 +ENSG00000104897 SF3A2 epididymis glandular cells High Enhanced Q15428 +ENSG00000104897 SF3A2 prostate glandular cells Medium Enhanced Q15428 +ENSG00000104897 SF3A2 seminal vesicle glandular cells Medium Enhanced Q15428 +ENSG00000104897 SF3A2 testis cells in seminiferous ducts Medium Enhanced Q15428 +ENSG00000104897 SF3A2 testis Leydig cells Medium Enhanced Q15428 +ENSG00000104901 DKKL1 testis elongated or late spermatids High Enhanced Q9UK85 +ENSG00000104901 DKKL1 testis round or early spermatids High Enhanced Q9UK85 +ENSG00000104941 RSPH6A testis cells in seminiferous ducts High Enhanced Q9H0K4 +ENSG00000104941 RSPH6A testis Leydig cells High Enhanced Q9H0K4 +ENSG00000104951 IL4I1 testis elongated or late spermatids High Enhanced Q96RQ9 +ENSG00000104951 IL4I1 testis Leydig cells Low Enhanced Q96RQ9 +ENSG00000104951 IL4I1 testis pachytene spermatocytes Low Enhanced Q96RQ9 +ENSG00000104951 IL4I1 testis round or early spermatids High Enhanced Q96RQ9 +ENSG00000104976 SNAPC2 epididymis glandular cells High Supported Q13487 +ENSG00000104976 SNAPC2 prostate glandular cells High Supported Q13487 +ENSG00000104976 SNAPC2 seminal vesicle glandular cells High Supported Q13487 +ENSG00000104976 SNAPC2 testis cells in seminiferous ducts High Supported Q13487 +ENSG00000104976 SNAPC2 testis Leydig cells High Supported Q13487 +ENSG00000104980 TIMM44 epididymis glandular cells Medium Supported O43615 +ENSG00000104980 TIMM44 prostate glandular cells Low Supported O43615 +ENSG00000104980 TIMM44 seminal vesicle glandular cells High Supported O43615 +ENSG00000104980 TIMM44 testis cells in seminiferous ducts High Supported O43615 +ENSG00000104980 TIMM44 testis Leydig cells High Supported O43615 +ENSG00000105085 MED26 testis cells in seminiferous ducts Low Enhanced O95402 +ENSG00000105127 AKAP8 epididymis glandular cells High Supported O43823 +ENSG00000105127 AKAP8 prostate glandular cells Medium Supported O43823 +ENSG00000105127 AKAP8 seminal vesicle glandular cells High Supported O43823 +ENSG00000105127 AKAP8 testis cells in seminiferous ducts High Supported O43823 +ENSG00000105127 AKAP8 testis Leydig cells High Supported O43823 +ENSG00000105143 SLC1A6 testis elongated or late spermatids High Enhanced P48664 +ENSG00000105143 SLC1A6 testis Leydig cells Medium Enhanced P48664 +ENSG00000105143 SLC1A6 testis pachytene spermatocytes Medium Enhanced P48664 +ENSG00000105143 SLC1A6 testis peritubular cells Low Enhanced P48664 +ENSG00000105143 SLC1A6 testis preleptotene spermatocytes Low Enhanced P48664 +ENSG00000105143 SLC1A6 testis round or early spermatids Low Enhanced P48664 +ENSG00000105143 SLC1A6 testis sertoli cells High Enhanced P48664 +ENSG00000105143 SLC1A6 testis spermatogonia Low Enhanced P48664 +ENSG00000105185 PDCD5 seminal vesicle glandular cells Low Enhanced O14737 +ENSG00000105185 PDCD5 testis cells in seminiferous ducts High Enhanced O14737 +ENSG00000105185 PDCD5 testis Leydig cells Medium Enhanced O14737 +ENSG00000105197 TIMM50 epididymis glandular cells Medium Enhanced Q3ZCQ8 +ENSG00000105197 TIMM50 prostate glandular cells Medium Enhanced Q3ZCQ8 +ENSG00000105197 TIMM50 seminal vesicle glandular cells Medium Enhanced Q3ZCQ8 +ENSG00000105197 TIMM50 testis cells in seminiferous ducts Medium Enhanced Q3ZCQ8 +ENSG00000105197 TIMM50 testis Leydig cells High Enhanced Q3ZCQ8 +ENSG00000105202 FBL epididymis glandular cells Medium Supported NA +ENSG00000105202 FBL prostate glandular cells Medium Supported NA +ENSG00000105202 FBL seminal vesicle glandular cells Medium Supported NA +ENSG00000105202 FBL testis cells in seminiferous ducts Medium Supported NA +ENSG00000105202 FBL testis Leydig cells Medium Supported NA +ENSG00000105220 GPI epididymis glandular cells Medium Enhanced P06744 +ENSG00000105220 GPI prostate glandular cells Medium Enhanced P06744 +ENSG00000105220 GPI seminal vesicle glandular cells Medium Enhanced P06744 +ENSG00000105220 GPI testis cells in seminiferous ducts Low Enhanced P06744 +ENSG00000105220 GPI testis Leydig cells Medium Enhanced P06744 +ENSG00000105255 FSD1 testis elongated or late spermatids Medium Supported Q9BTV5 +ENSG00000105255 FSD1 testis Leydig cells Low Supported Q9BTV5 +ENSG00000105255 FSD1 testis pachytene spermatocytes Low Supported Q9BTV5 +ENSG00000105255 FSD1 testis preleptotene spermatocytes High Supported Q9BTV5 +ENSG00000105255 FSD1 testis round or early spermatids Low Supported Q9BTV5 +ENSG00000105255 FSD1 testis spermatogonia High Supported Q9BTV5 +ENSG00000105281 SLC1A5 epididymis glandular cells High Enhanced Q15758 +ENSG00000105281 SLC1A5 prostate glandular cells High Enhanced Q15758 +ENSG00000105281 SLC1A5 seminal vesicle glandular cells Medium Enhanced Q15758 +ENSG00000105281 SLC1A5 testis cells in seminiferous ducts Medium Enhanced Q15758 +ENSG00000105281 SLC1A5 testis Leydig cells Low Enhanced Q15758 +ENSG00000105287 PRKD2 epididymis glandular cells Medium Enhanced Q9BZL6 +ENSG00000105287 PRKD2 prostate glandular cells Low Enhanced Q9BZL6 +ENSG00000105287 PRKD2 seminal vesicle glandular cells Low Enhanced Q9BZL6 +ENSG00000105287 PRKD2 testis cells in seminiferous ducts Low Enhanced Q9BZL6 +ENSG00000105287 PRKD2 testis Leydig cells Medium Enhanced Q9BZL6 +ENSG00000105289 TJP3 epididymis glandular cells Medium Enhanced O95049 +ENSG00000105289 TJP3 prostate glandular cells Low Enhanced O95049 +ENSG00000105289 TJP3 seminal vesicle glandular cells Medium Enhanced O95049 +ENSG00000105289 TJP3 testis cells in seminiferous ducts Low Enhanced O95049 +ENSG00000105289 TJP3 testis Leydig cells Low Enhanced O95049 +ENSG00000105323 HNRNPUL1 epididymis glandular cells High Enhanced Q9BUJ2 +ENSG00000105323 HNRNPUL1 prostate glandular cells High Enhanced Q9BUJ2 +ENSG00000105323 HNRNPUL1 seminal vesicle glandular cells High Enhanced Q9BUJ2 +ENSG00000105323 HNRNPUL1 testis cells in seminiferous ducts High Enhanced Q9BUJ2 +ENSG00000105323 HNRNPUL1 testis Leydig cells High Enhanced Q9BUJ2 +ENSG00000105357 MYH14 epididymis glandular cells Medium Enhanced Q7Z406 +ENSG00000105357 MYH14 prostate glandular cells Low Enhanced Q7Z406 +ENSG00000105357 MYH14 seminal vesicle glandular cells Medium Enhanced Q7Z406 +ENSG00000105379 ETFB epididymis glandular cells Medium Supported P38117 +ENSG00000105379 ETFB prostate glandular cells High Supported P38117 +ENSG00000105379 ETFB seminal vesicle glandular cells High Supported P38117 +ENSG00000105379 ETFB testis cells in seminiferous ducts High Supported P38117 +ENSG00000105379 ETFB testis Leydig cells High Supported P38117 +ENSG00000105398 SULT2A1 epididymis glandular cells Low Enhanced Q06520 +ENSG00000105398 SULT2A1 testis Leydig cells Low Enhanced Q06520 +ENSG00000105401 CDC37 epididymis glandular cells Medium Supported Q16543 +ENSG00000105401 CDC37 prostate glandular cells Medium Supported Q16543 +ENSG00000105401 CDC37 seminal vesicle glandular cells Low Supported Q16543 +ENSG00000105401 CDC37 testis cells in seminiferous ducts Medium Supported Q16543 +ENSG00000105401 CDC37 testis Leydig cells Low Supported Q16543 +ENSG00000105404 RABAC1 epididymis glandular cells High Enhanced Q9UI14 +ENSG00000105404 RABAC1 prostate glandular cells High Enhanced Q9UI14 +ENSG00000105404 RABAC1 seminal vesicle glandular cells High Enhanced Q9UI14 +ENSG00000105404 RABAC1 testis cells in seminiferous ducts High Enhanced Q9UI14 +ENSG00000105404 RABAC1 testis Leydig cells High Enhanced Q9UI14 +ENSG00000105467 SYNGR4 testis cells in seminiferous ducts High Enhanced O95473 +ENSG00000105483 CARD8 epididymis glandular cells Medium Supported Q9Y2G2 +ENSG00000105483 CARD8 prostate glandular cells Medium Supported Q9Y2G2 +ENSG00000105483 CARD8 seminal vesicle glandular cells Medium Supported Q9Y2G2 +ENSG00000105483 CARD8 testis cells in seminiferous ducts Medium Supported Q9Y2G2 +ENSG00000105483 CARD8 testis Leydig cells Medium Supported Q9Y2G2 +ENSG00000105552 BCAT2 epididymis glandular cells Medium Enhanced O15382 +ENSG00000105552 BCAT2 prostate glandular cells High Enhanced O15382 +ENSG00000105552 BCAT2 seminal vesicle glandular cells High Enhanced O15382 +ENSG00000105552 BCAT2 testis cells in seminiferous ducts High Enhanced O15382 +ENSG00000105552 BCAT2 testis Leydig cells High Enhanced O15382 +ENSG00000105607 GCDH epididymis glandular cells Low Enhanced Q92947 +ENSG00000105607 GCDH prostate glandular cells High Enhanced Q92947 +ENSG00000105607 GCDH seminal vesicle glandular cells High Enhanced Q92947 +ENSG00000105607 GCDH testis cells in seminiferous ducts Low Enhanced Q92947 +ENSG00000105607 GCDH testis Leydig cells Medium Enhanced Q92947 +ENSG00000105612 DNASE2 epididymis glandular cells Medium Enhanced O00115 +ENSG00000105612 DNASE2 prostate glandular cells Medium Enhanced O00115 +ENSG00000105612 DNASE2 seminal vesicle glandular cells Low Enhanced O00115 +ENSG00000105612 DNASE2 testis Leydig cells Low Enhanced O00115 +ENSG00000105613 MAST1 testis cells in seminiferous ducts Low Enhanced Q9Y2H9 +ENSG00000105618 PRPF31 epididymis glandular cells High Supported NA +ENSG00000105618 PRPF31 prostate glandular cells High Supported NA +ENSG00000105618 PRPF31 seminal vesicle glandular cells High Supported NA +ENSG00000105618 PRPF31 testis cells in seminiferous ducts High Supported NA +ENSG00000105618 PRPF31 testis Leydig cells High Supported NA +ENSG00000105655 ISYNA1 epididymis glandular cells Low Enhanced Q9NPH2 +ENSG00000105655 ISYNA1 prostate glandular cells Medium Enhanced Q9NPH2 +ENSG00000105655 ISYNA1 seminal vesicle glandular cells Medium Enhanced Q9NPH2 +ENSG00000105655 ISYNA1 testis elongated or late spermatids High Enhanced Q9NPH2 +ENSG00000105655 ISYNA1 testis pachytene spermatocytes High Enhanced Q9NPH2 +ENSG00000105655 ISYNA1 testis preleptotene spermatocytes High Enhanced Q9NPH2 +ENSG00000105655 ISYNA1 testis round or early spermatids High Enhanced Q9NPH2 +ENSG00000105655 ISYNA1 testis sertoli cells High Enhanced Q9NPH2 +ENSG00000105655 ISYNA1 testis spermatogonia High Enhanced Q9NPH2 +ENSG00000105669 COPE epididymis glandular cells High Supported O14579 +ENSG00000105669 COPE prostate glandular cells Medium Supported O14579 +ENSG00000105669 COPE seminal vesicle glandular cells Medium Supported O14579 +ENSG00000105669 COPE testis cells in seminiferous ducts Medium Supported O14579 +ENSG00000105669 COPE testis Leydig cells Medium Supported O14579 +ENSG00000105671 DDX49 epididymis glandular cells Medium Enhanced Q9Y6V7 +ENSG00000105671 DDX49 prostate glandular cells High Enhanced Q9Y6V7 +ENSG00000105671 DDX49 seminal vesicle glandular cells High Enhanced Q9Y6V7 +ENSG00000105671 DDX49 testis cells in seminiferous ducts High Enhanced Q9Y6V7 +ENSG00000105671 DDX49 testis Leydig cells High Enhanced Q9Y6V7 +ENSG00000105676 ARMC6 prostate glandular cells Medium Supported Q6NXE6 +ENSG00000105676 ARMC6 seminal vesicle glandular cells Medium Supported Q6NXE6 +ENSG00000105676 ARMC6 testis cells in seminiferous ducts Medium Supported Q6NXE6 +ENSG00000105676 ARMC6 testis Leydig cells Medium Supported Q6NXE6 +ENSG00000105679 GAPDHS testis elongated or late spermatids High Enhanced O14556 +ENSG00000105701 FKBP8 epididymis glandular cells Medium Supported Q14318 +ENSG00000105701 FKBP8 prostate glandular cells Medium Supported Q14318 +ENSG00000105701 FKBP8 seminal vesicle glandular cells High Supported Q14318 +ENSG00000105701 FKBP8 testis cells in seminiferous ducts High Supported Q14318 +ENSG00000105701 FKBP8 testis Leydig cells High Supported Q14318 +ENSG00000105717 PBX4 testis elongated or late spermatids High Enhanced Q9BYU1 +ENSG00000105717 PBX4 testis sertoli cells High Enhanced Q9BYU1 +ENSG00000105755 ETHE1 epididymis glandular cells Medium Enhanced O95571 +ENSG00000105755 ETHE1 prostate glandular cells Medium Enhanced O95571 +ENSG00000105755 ETHE1 seminal vesicle glandular cells Medium Enhanced O95571 +ENSG00000105755 ETHE1 testis cells in seminiferous ducts Medium Enhanced O95571 +ENSG00000105755 ETHE1 testis Leydig cells Low Enhanced O95571 +ENSG00000105767 CADM4 prostate glandular cells Low Enhanced Q8NFZ8 +ENSG00000105767 CADM4 seminal vesicle glandular cells Low Enhanced Q8NFZ8 +ENSG00000105767 CADM4 testis Leydig cells Low Enhanced Q8NFZ8 +ENSG00000105810 CDK6 epididymis glandular cells Low Enhanced Q00534 +ENSG00000105810 CDK6 prostate glandular cells Low Enhanced Q00534 +ENSG00000105810 CDK6 seminal vesicle glandular cells Low Enhanced Q00534 +ENSG00000105810 CDK6 testis cells in seminiferous ducts Low Enhanced Q00534 +ENSG00000105810 CDK6 testis Leydig cells Medium Enhanced Q00534 +ENSG00000105854 PON2 epididymis glandular cells High Enhanced Q15165 +ENSG00000105854 PON2 prostate glandular cells Medium Enhanced Q15165 +ENSG00000105854 PON2 seminal vesicle glandular cells Medium Enhanced Q15165 +ENSG00000105854 PON2 testis cells in seminiferous ducts High Enhanced Q15165 +ENSG00000105854 PON2 testis Leydig cells High Enhanced Q15165 +ENSG00000105855 ITGB8 epididymis glandular cells Medium Supported P26012 +ENSG00000105855 ITGB8 prostate glandular cells Low Supported P26012 +ENSG00000105855 ITGB8 seminal vesicle glandular cells Medium Supported P26012 +ENSG00000105855 ITGB8 testis Leydig cells Low Supported P26012 +ENSG00000105879 CBLL1 epididymis glandular cells Medium Enhanced Q75N03 +ENSG00000105879 CBLL1 prostate glandular cells Medium Enhanced Q75N03 +ENSG00000105879 CBLL1 seminal vesicle glandular cells Medium Enhanced Q75N03 +ENSG00000105879 CBLL1 testis cells in seminiferous ducts Medium Enhanced Q75N03 +ENSG00000105879 CBLL1 testis Leydig cells Medium Enhanced Q75N03 +ENSG00000105894 PTN testis cells in seminiferous ducts High Enhanced P21246 +ENSG00000105926 MPP6 epididymis glandular cells Low Enhanced Q9NZW5 +ENSG00000105926 MPP6 prostate glandular cells Medium Enhanced Q9NZW5 +ENSG00000105926 MPP6 testis elongated or late spermatids High Enhanced Q9NZW5 +ENSG00000105926 MPP6 testis Leydig cells Low Enhanced Q9NZW5 +ENSG00000105926 MPP6 testis pachytene spermatocytes High Enhanced Q9NZW5 +ENSG00000105926 MPP6 testis preleptotene spermatocytes High Enhanced Q9NZW5 +ENSG00000105926 MPP6 testis round or early spermatids High Enhanced Q9NZW5 +ENSG00000105926 MPP6 testis spermatogonia High Enhanced Q9NZW5 +ENSG00000105948 TTC26 seminal vesicle glandular cells Low Enhanced A0AVF1 +ENSG00000105948 TTC26 testis cells in seminiferous ducts Low Enhanced A0AVF1 +ENSG00000105953 OGDH epididymis glandular cells Medium Supported Q02218 +ENSG00000105953 OGDH prostate glandular cells Medium Supported Q02218 +ENSG00000105953 OGDH seminal vesicle glandular cells High Supported Q02218 +ENSG00000105953 OGDH testis cells in seminiferous ducts Medium Supported Q02218 +ENSG00000105953 OGDH testis Leydig cells High Supported Q02218 +ENSG00000105963 ADAP1 epididymis glandular cells Low Enhanced O75689 +ENSG00000105963 ADAP1 seminal vesicle glandular cells Low Enhanced O75689 +ENSG00000105963 ADAP1 testis cells in seminiferous ducts Low Enhanced O75689 +ENSG00000105963 ADAP1 testis Leydig cells Low Enhanced O75689 +ENSG00000105968 H2AFV epididymis glandular cells Medium Supported Q71UI9 +ENSG00000105968 H2AFV prostate glandular cells Low Supported Q71UI9 +ENSG00000105968 H2AFV seminal vesicle glandular cells Low Supported Q71UI9 +ENSG00000105968 H2AFV testis cells in seminiferous ducts Medium Supported Q71UI9 +ENSG00000105968 H2AFV testis Leydig cells Medium Supported Q71UI9 +ENSG00000105971 CAV2 testis Leydig cells Medium Enhanced P51636 +ENSG00000105974 CAV1 prostate glandular cells Medium Enhanced Q03135 +ENSG00000105982 RNF32 testis cells in seminiferous ducts High Enhanced Q9H0A6 +ENSG00000105993 DNAJB6 epididymis glandular cells Medium Enhanced O75190 +ENSG00000105993 DNAJB6 prostate glandular cells Low Enhanced O75190 +ENSG00000105993 DNAJB6 seminal vesicle glandular cells Low Enhanced O75190 +ENSG00000105993 DNAJB6 testis cells in seminiferous ducts Medium Enhanced O75190 +ENSG00000105993 DNAJB6 testis Leydig cells Medium Enhanced O75190 +ENSG00000106028 SSBP1 epididymis glandular cells Medium Enhanced E7EUY5 +ENSG00000106028 SSBP1 prostate glandular cells Low Enhanced E7EUY5 +ENSG00000106028 SSBP1 seminal vesicle glandular cells Medium Enhanced E7EUY5 +ENSG00000106028 SSBP1 testis cells in seminiferous ducts Medium Enhanced E7EUY5 +ENSG00000106028 SSBP1 testis Leydig cells Medium Enhanced E7EUY5 +ENSG00000106049 HIBADH epididymis glandular cells Low Enhanced P31937 +ENSG00000106049 HIBADH prostate glandular cells Medium Enhanced P31937 +ENSG00000106049 HIBADH seminal vesicle glandular cells Medium Enhanced P31937 +ENSG00000106049 HIBADH testis cells in seminiferous ducts Medium Enhanced P31937 +ENSG00000106049 HIBADH testis Leydig cells High Enhanced P31937 +ENSG00000106066 CPVL seminal vesicle glandular cells Medium Enhanced Q9H3G5 +ENSG00000106066 CPVL testis cells in seminiferous ducts Low Enhanced Q9H3G5 +ENSG00000106066 CPVL testis Leydig cells Low Enhanced Q9H3G5 +ENSG00000106078 COBL epididymis glandular cells Medium Enhanced O75128 +ENSG00000106078 COBL prostate glandular cells High Enhanced O75128 +ENSG00000106078 COBL seminal vesicle glandular cells High Enhanced O75128 +ENSG00000106078 COBL testis cells in seminiferous ducts Medium Enhanced O75128 +ENSG00000106078 COBL testis Leydig cells High Enhanced O75128 +ENSG00000106105 GARS epididymis glandular cells Medium Enhanced P41250 +ENSG00000106105 GARS prostate glandular cells Medium Enhanced P41250 +ENSG00000106105 GARS seminal vesicle glandular cells Medium Enhanced P41250 +ENSG00000106105 GARS testis cells in seminiferous ducts High Enhanced P41250 +ENSG00000106105 GARS testis Leydig cells Medium Enhanced P41250 +ENSG00000106211 HSPB1 epididymis glandular cells High Enhanced P04792 +ENSG00000106211 HSPB1 prostate glandular cells Medium Enhanced P04792 +ENSG00000106211 HSPB1 seminal vesicle glandular cells Medium Enhanced P04792 +ENSG00000106211 HSPB1 testis Leydig cells Low Enhanced P04792 +ENSG00000106236 NPTX2 testis elongated or late spermatids Low Supported P47972 +ENSG00000106236 NPTX2 testis pachytene spermatocytes Low Supported P47972 +ENSG00000106236 NPTX2 testis round or early spermatids Low Supported P47972 +ENSG00000106299 WASL epididymis glandular cells High Supported O00401 +ENSG00000106299 WASL prostate glandular cells High Supported O00401 +ENSG00000106299 WASL seminal vesicle glandular cells High Supported O00401 +ENSG00000106299 WASL testis cells in seminiferous ducts High Supported O00401 +ENSG00000106299 WASL testis Leydig cells Medium Supported O00401 +ENSG00000106304 SPAM1 testis elongated or late spermatids High Enhanced P38567 +ENSG00000106304 SPAM1 testis pachytene spermatocytes High Enhanced P38567 +ENSG00000106304 SPAM1 testis preleptotene spermatocytes Medium Enhanced P38567 +ENSG00000106304 SPAM1 testis round or early spermatids High Enhanced P38567 +ENSG00000106304 SPAM1 testis spermatogonia Medium Enhanced P38567 +ENSG00000106305 AIMP2 epididymis glandular cells Medium Supported Q13155 +ENSG00000106305 AIMP2 prostate glandular cells Medium Supported Q13155 +ENSG00000106305 AIMP2 seminal vesicle glandular cells Low Supported Q13155 +ENSG00000106305 AIMP2 testis cells in seminiferous ducts Medium Supported Q13155 +ENSG00000106305 AIMP2 testis Leydig cells Medium Supported Q13155 +ENSG00000106336 FBXO24 testis preleptotene spermatocytes Medium Enhanced O75426 +ENSG00000106336 FBXO24 testis spermatogonia Medium Enhanced O75426 +ENSG00000106341 PPP1R17 testis preleptotene spermatocytes Medium Supported O96001 +ENSG00000106341 PPP1R17 testis spermatogonia High Supported O96001 +ENSG00000106344 RBM28 epididymis glandular cells Medium Enhanced Q9NW13 +ENSG00000106344 RBM28 prostate glandular cells Medium Enhanced Q9NW13 +ENSG00000106344 RBM28 seminal vesicle glandular cells Medium Enhanced Q9NW13 +ENSG00000106344 RBM28 testis cells in seminiferous ducts Medium Enhanced Q9NW13 +ENSG00000106344 RBM28 testis Leydig cells Medium Enhanced Q9NW13 +ENSG00000106367 AP1S1 prostate glandular cells Medium Supported P61966 +ENSG00000106367 AP1S1 testis cells in seminiferous ducts Medium Supported P61966 +ENSG00000106367 AP1S1 testis Leydig cells Medium Supported P61966 +ENSG00000106392 C1GALT1 epididymis glandular cells Medium Enhanced Q9NS00 +ENSG00000106392 C1GALT1 prostate glandular cells High Enhanced Q9NS00 +ENSG00000106392 C1GALT1 seminal vesicle glandular cells High Enhanced Q9NS00 +ENSG00000106392 C1GALT1 testis cells in seminiferous ducts Low Enhanced Q9NS00 +ENSG00000106392 C1GALT1 testis Leydig cells Medium Enhanced Q9NS00 +ENSG00000106443 PHF14 epididymis glandular cells High Supported O94880 +ENSG00000106443 PHF14 prostate glandular cells High Supported O94880 +ENSG00000106443 PHF14 seminal vesicle glandular cells High Supported O94880 +ENSG00000106443 PHF14 testis cells in seminiferous ducts High Supported O94880 +ENSG00000106462 EZH2 epididymis glandular cells Low Enhanced Q15910 +ENSG00000106462 EZH2 testis elongated or late spermatids Medium Enhanced Q15910 +ENSG00000106462 EZH2 testis pachytene spermatocytes High Enhanced Q15910 +ENSG00000106462 EZH2 testis preleptotene spermatocytes High Enhanced Q15910 +ENSG00000106462 EZH2 testis round or early spermatids High Enhanced Q15910 +ENSG00000106462 EZH2 testis spermatogonia High Enhanced Q15910 +ENSG00000106483 SFRP4 testis cells in seminiferous ducts Low Enhanced Q6FHJ7 +ENSG00000106541 AGR2 epididymis glandular cells High Enhanced O95994 +ENSG00000106541 AGR2 prostate glandular cells High Enhanced O95994 +ENSG00000106541 AGR2 seminal vesicle glandular cells High Enhanced O95994 +ENSG00000106546 AHR epididymis glandular cells Medium Enhanced P35869 +ENSG00000106546 AHR seminal vesicle glandular cells Medium Enhanced P35869 +ENSG00000106546 AHR testis cells in seminiferous ducts Low Enhanced P35869 +ENSG00000106546 AHR testis Leydig cells Medium Enhanced P35869 +ENSG00000106554 CHCHD3 epididymis glandular cells Medium Enhanced Q9NX63 +ENSG00000106554 CHCHD3 prostate glandular cells High Enhanced Q9NX63 +ENSG00000106554 CHCHD3 seminal vesicle glandular cells High Enhanced Q9NX63 +ENSG00000106554 CHCHD3 testis cells in seminiferous ducts Medium Enhanced Q9NX63 +ENSG00000106554 CHCHD3 testis Leydig cells High Enhanced Q9NX63 +ENSG00000106624 AEBP1 epididymis glandular cells Low Enhanced Q8IUX7 +ENSG00000106624 AEBP1 seminal vesicle glandular cells Low Enhanced Q8IUX7 +ENSG00000106624 AEBP1 testis cells in seminiferous ducts Low Enhanced Q8IUX7 +ENSG00000106648 GALNTL5 testis elongated or late spermatids High Enhanced Q7Z4T8 +ENSG00000106648 GALNTL5 testis Leydig cells Low Enhanced Q7Z4T8 +ENSG00000106648 GALNTL5 testis pachytene spermatocytes High Enhanced Q7Z4T8 +ENSG00000106648 GALNTL5 testis preleptotene spermatocytes Low Enhanced Q7Z4T8 +ENSG00000106648 GALNTL5 testis round or early spermatids High Enhanced Q7Z4T8 +ENSG00000106648 GALNTL5 testis spermatogonia Low Enhanced Q7Z4T8 +ENSG00000106665 CLIP2 epididymis glandular cells Medium Enhanced Q9UDT6 +ENSG00000106665 CLIP2 prostate glandular cells Medium Enhanced Q9UDT6 +ENSG00000106665 CLIP2 seminal vesicle glandular cells Medium Enhanced Q9UDT6 +ENSG00000106665 CLIP2 testis cells in seminiferous ducts Low Enhanced Q9UDT6 +ENSG00000106665 CLIP2 testis Leydig cells Medium Enhanced Q9UDT6 +ENSG00000106686 SPATA6L testis elongated or late spermatids Low Enhanced Q8N4H0 +ENSG00000106686 SPATA6L testis Leydig cells Low Enhanced Q8N4H0 +ENSG00000106686 SPATA6L testis pachytene spermatocytes Medium Enhanced Q8N4H0 +ENSG00000106686 SPATA6L testis peritubular cells Low Enhanced Q8N4H0 +ENSG00000106686 SPATA6L testis preleptotene spermatocytes Medium Enhanced Q8N4H0 +ENSG00000106686 SPATA6L testis round or early spermatids Low Enhanced Q8N4H0 +ENSG00000106686 SPATA6L testis sertoli cells Medium Enhanced Q8N4H0 +ENSG00000106686 SPATA6L testis spermatogonia High Enhanced Q8N4H0 +ENSG00000106789 CORO2A epididymis glandular cells Low Enhanced Q92828 +ENSG00000106789 CORO2A prostate glandular cells Medium Enhanced Q92828 +ENSG00000106789 CORO2A testis cells in seminiferous ducts Medium Enhanced Q92828 +ENSG00000106789 CORO2A testis Leydig cells Low Enhanced Q92828 +ENSG00000106853 PTGR1 epididymis glandular cells Low Enhanced Q14914 +ENSG00000106853 PTGR1 seminal vesicle glandular cells Low Enhanced Q14914 +ENSG00000106853 PTGR1 testis cells in seminiferous ducts Low Enhanced Q14914 +ENSG00000106853 PTGR1 testis Leydig cells Low Enhanced Q14914 +ENSG00000106992 AK1 seminal vesicle glandular cells Low Enhanced P00568 +ENSG00000106992 AK1 testis cells in seminiferous ducts Low Enhanced P00568 +ENSG00000106992 AK1 testis Leydig cells Low Enhanced P00568 +ENSG00000107020 PLGRKT epididymis glandular cells High Enhanced Q9HBL7 +ENSG00000107020 PLGRKT prostate glandular cells High Enhanced Q9HBL7 +ENSG00000107020 PLGRKT seminal vesicle glandular cells High Enhanced Q9HBL7 +ENSG00000107020 PLGRKT testis cells in seminiferous ducts Low Enhanced Q9HBL7 +ENSG00000107020 PLGRKT testis Leydig cells Medium Enhanced Q9HBL7 +ENSG00000107036 RIC1 epididymis glandular cells High Supported Q4ADV7 +ENSG00000107036 RIC1 prostate glandular cells High Supported Q4ADV7 +ENSG00000107036 RIC1 seminal vesicle glandular cells High Supported Q4ADV7 +ENSG00000107036 RIC1 testis cells in seminiferous ducts Low Supported Q4ADV7 +ENSG00000107036 RIC1 testis Leydig cells High Supported Q4ADV7 +ENSG00000107099 DOCK8 epididymis glandular cells Medium Enhanced Q8NF50 +ENSG00000107099 DOCK8 prostate glandular cells Medium Enhanced Q8NF50 +ENSG00000107099 DOCK8 testis cells in seminiferous ducts Medium Enhanced Q8NF50 +ENSG00000107099 DOCK8 testis Leydig cells Low Enhanced Q8NF50 +ENSG00000107105 ELAVL2 prostate glandular cells Low Enhanced Q12926 +ENSG00000107105 ELAVL2 testis preleptotene spermatocytes High Enhanced Q12926 +ENSG00000107105 ELAVL2 testis spermatogonia High Enhanced Q12926 +ENSG00000107262 BAG1 epididymis glandular cells High Enhanced Q99933 +ENSG00000107262 BAG1 prostate glandular cells High Enhanced Q99933 +ENSG00000107262 BAG1 seminal vesicle glandular cells Low Enhanced Q99933 +ENSG00000107262 BAG1 testis cells in seminiferous ducts Medium Enhanced Q99933 +ENSG00000107262 BAG1 testis Leydig cells Low Enhanced Q99933 +ENSG00000107371 EXOSC3 epididymis glandular cells Medium Enhanced Q9NQT5 +ENSG00000107371 EXOSC3 prostate glandular cells Medium Enhanced Q9NQT5 +ENSG00000107371 EXOSC3 seminal vesicle glandular cells Medium Enhanced Q9NQT5 +ENSG00000107371 EXOSC3 testis cells in seminiferous ducts High Enhanced Q9NQT5 +ENSG00000107371 EXOSC3 testis Leydig cells Medium Enhanced Q9NQT5 +ENSG00000107485 GATA3 epididymis glandular cells Medium Enhanced P23771 +ENSG00000107485 GATA3 seminal vesicle glandular cells Medium Enhanced P23771 +ENSG00000107485 GATA3 testis Leydig cells Low Enhanced P23771 +ENSG00000107537 PHYH epididymis glandular cells Medium Enhanced O14832 +ENSG00000107537 PHYH prostate glandular cells Medium Enhanced O14832 +ENSG00000107537 PHYH seminal vesicle glandular cells Medium Enhanced O14832 +ENSG00000107537 PHYH testis cells in seminiferous ducts Medium Enhanced O14832 +ENSG00000107537 PHYH testis Leydig cells Medium Enhanced O14832 +ENSG00000107581 EIF3A epididymis glandular cells Medium Enhanced Q14152 +ENSG00000107581 EIF3A prostate glandular cells Medium Enhanced Q14152 +ENSG00000107581 EIF3A seminal vesicle glandular cells Medium Enhanced Q14152 +ENSG00000107581 EIF3A testis cells in seminiferous ducts Medium Enhanced Q14152 +ENSG00000107581 EIF3A testis Leydig cells Medium Enhanced Q14152 +ENSG00000107742 SPOCK2 epididymis glandular cells Low Supported Q92563 +ENSG00000107742 SPOCK2 prostate glandular cells Low Supported Q92563 +ENSG00000107742 SPOCK2 seminal vesicle glandular cells Low Supported Q92563 +ENSG00000107742 SPOCK2 testis cells in seminiferous ducts Medium Supported Q92563 +ENSG00000107742 SPOCK2 testis Leydig cells Medium Supported Q92563 +ENSG00000107798 LIPA epididymis glandular cells Low Enhanced P38571 +ENSG00000107798 LIPA prostate glandular cells Low Enhanced P38571 +ENSG00000107882 SUFU epididymis glandular cells Medium Enhanced Q9UMX1 +ENSG00000107882 SUFU prostate glandular cells Medium Enhanced Q9UMX1 +ENSG00000107882 SUFU seminal vesicle glandular cells Medium Enhanced Q9UMX1 +ENSG00000107882 SUFU testis cells in seminiferous ducts Medium Enhanced Q9UMX1 +ENSG00000107882 SUFU testis Leydig cells Medium Enhanced Q9UMX1 +ENSG00000107897 ACBD5 epididymis glandular cells Medium Enhanced Q5T8D3 +ENSG00000107897 ACBD5 prostate glandular cells High Enhanced Q5T8D3 +ENSG00000107897 ACBD5 seminal vesicle glandular cells High Enhanced Q5T8D3 +ENSG00000107897 ACBD5 testis cells in seminiferous ducts High Enhanced Q5T8D3 +ENSG00000107897 ACBD5 testis Leydig cells High Enhanced Q5T8D3 +ENSG00000107902 LHPP epididymis glandular cells Medium Enhanced Q9H008 +ENSG00000107902 LHPP prostate glandular cells Low Enhanced Q9H008 +ENSG00000107902 LHPP seminal vesicle glandular cells Medium Enhanced Q9H008 +ENSG00000107902 LHPP testis cells in seminiferous ducts Medium Enhanced Q9H008 +ENSG00000107902 LHPP testis Leydig cells Medium Enhanced Q9H008 +ENSG00000107959 PITRM1 epididymis glandular cells High Enhanced Q5JRX3 +ENSG00000107959 PITRM1 prostate glandular cells Medium Enhanced Q5JRX3 +ENSG00000107959 PITRM1 seminal vesicle glandular cells Medium Enhanced Q5JRX3 +ENSG00000107959 PITRM1 testis cells in seminiferous ducts High Enhanced Q5JRX3 +ENSG00000107959 PITRM1 testis Leydig cells Medium Enhanced Q5JRX3 +ENSG00000107968 MAP3K8 epididymis glandular cells High Supported P41279 +ENSG00000107968 MAP3K8 prostate glandular cells Medium Supported P41279 +ENSG00000107968 MAP3K8 seminal vesicle glandular cells Medium Supported P41279 +ENSG00000107968 MAP3K8 testis cells in seminiferous ducts High Supported P41279 +ENSG00000107968 MAP3K8 testis Leydig cells High Supported P41279 +ENSG00000108039 XPNPEP1 epididymis glandular cells Low Supported Q9NQW7 +ENSG00000108039 XPNPEP1 prostate glandular cells Medium Supported Q9NQW7 +ENSG00000108039 XPNPEP1 seminal vesicle glandular cells Low Supported Q9NQW7 +ENSG00000108039 XPNPEP1 testis cells in seminiferous ducts Low Supported Q9NQW7 +ENSG00000108064 TFAM epididymis glandular cells Low Supported Q00059 +ENSG00000108064 TFAM prostate glandular cells Low Supported Q00059 +ENSG00000108064 TFAM seminal vesicle glandular cells Medium Supported Q00059 +ENSG00000108064 TFAM testis cells in seminiferous ducts Medium Supported Q00059 +ENSG00000108064 TFAM testis Leydig cells Medium Supported Q00059 +ENSG00000108091 CCDC6 epididymis glandular cells Low Enhanced Q16204 +ENSG00000108091 CCDC6 prostate glandular cells Low Enhanced Q16204 +ENSG00000108091 CCDC6 testis cells in seminiferous ducts Medium Enhanced Q16204 +ENSG00000108091 CCDC6 testis Leydig cells Medium Enhanced Q16204 +ENSG00000108176 DNAJC12 epididymis glandular cells Medium Enhanced Q9UKB3 +ENSG00000108176 DNAJC12 prostate glandular cells Medium Enhanced Q9UKB3 +ENSG00000108176 DNAJC12 seminal vesicle glandular cells Medium Enhanced Q9UKB3 +ENSG00000108176 DNAJC12 testis cells in seminiferous ducts Low Enhanced Q9UKB3 +ENSG00000108176 DNAJC12 testis Leydig cells Medium Enhanced Q9UKB3 +ENSG00000108312 UBTF epididymis glandular cells High Enhanced P17480 +ENSG00000108312 UBTF prostate glandular cells Medium Enhanced P17480 +ENSG00000108312 UBTF seminal vesicle glandular cells Medium Enhanced P17480 +ENSG00000108312 UBTF testis cells in seminiferous ducts Medium Enhanced P17480 +ENSG00000108312 UBTF testis Leydig cells High Enhanced P17480 +ENSG00000108381 ASPA testis Leydig cells Medium Enhanced P45381 +ENSG00000108424 KPNB1 epididymis glandular cells Medium Enhanced Q14974 +ENSG00000108424 KPNB1 prostate glandular cells Low Enhanced Q14974 +ENSG00000108424 KPNB1 seminal vesicle glandular cells Medium Enhanced Q14974 +ENSG00000108424 KPNB1 testis cells in seminiferous ducts High Enhanced Q14974 +ENSG00000108424 KPNB1 testis Leydig cells Medium Enhanced Q14974 +ENSG00000108439 PNPO epididymis glandular cells Medium Enhanced Q9NVS9 +ENSG00000108439 PNPO prostate glandular cells Medium Enhanced Q9NVS9 +ENSG00000108439 PNPO seminal vesicle glandular cells Medium Enhanced Q9NVS9 +ENSG00000108439 PNPO testis cells in seminiferous ducts Medium Enhanced Q9NVS9 +ENSG00000108439 PNPO testis Leydig cells Medium Enhanced Q9NVS9 +ENSG00000108465 CDK5RAP3 epididymis glandular cells High Supported Q96JB5 +ENSG00000108465 CDK5RAP3 prostate glandular cells Medium Supported Q96JB5 +ENSG00000108465 CDK5RAP3 seminal vesicle glandular cells High Supported Q96JB5 +ENSG00000108465 CDK5RAP3 testis cells in seminiferous ducts High Supported Q96JB5 +ENSG00000108465 CDK5RAP3 testis Leydig cells Medium Supported Q96JB5 +ENSG00000108468 CBX1 epididymis glandular cells Medium Supported P83916 +ENSG00000108468 CBX1 prostate glandular cells Medium Supported P83916 +ENSG00000108468 CBX1 seminal vesicle glandular cells High Supported P83916 +ENSG00000108468 CBX1 testis cells in seminiferous ducts High Supported P83916 +ENSG00000108468 CBX1 testis Leydig cells Medium Supported P83916 +ENSG00000108518 PFN1 epididymis glandular cells Medium Enhanced P07737 +ENSG00000108518 PFN1 prostate glandular cells Medium Enhanced P07737 +ENSG00000108518 PFN1 seminal vesicle glandular cells Low Enhanced P07737 +ENSG00000108518 PFN1 testis cells in seminiferous ducts Medium Enhanced P07737 +ENSG00000108518 PFN1 testis Leydig cells Medium Enhanced P07737 +ENSG00000108561 C1QBP epididymis glandular cells Medium Supported Q07021 +ENSG00000108561 C1QBP prostate glandular cells Medium Supported Q07021 +ENSG00000108561 C1QBP seminal vesicle glandular cells Medium Supported Q07021 +ENSG00000108561 C1QBP testis cells in seminiferous ducts High Supported Q07021 +ENSG00000108561 C1QBP testis Leydig cells Medium Supported Q07021 +ENSG00000108578 BLMH epididymis glandular cells Low Enhanced Q13867 +ENSG00000108578 BLMH testis cells in seminiferous ducts Low Enhanced Q13867 +ENSG00000108592 FTSJ3 epididymis glandular cells High Supported Q8IY81 +ENSG00000108592 FTSJ3 seminal vesicle glandular cells Low Supported Q8IY81 +ENSG00000108592 FTSJ3 testis cells in seminiferous ducts Low Supported Q8IY81 +ENSG00000108592 FTSJ3 testis Leydig cells Medium Supported Q8IY81 +ENSG00000108602 ALDH3A1 epididymis glandular cells Medium Enhanced P30838 +ENSG00000108602 ALDH3A1 prostate glandular cells Low Enhanced P30838 +ENSG00000108602 ALDH3A1 seminal vesicle glandular cells Low Enhanced P30838 +ENSG00000108651 UTP6 epididymis glandular cells Low Enhanced Q9NYH9 +ENSG00000108651 UTP6 prostate glandular cells Low Enhanced Q9NYH9 +ENSG00000108651 UTP6 seminal vesicle glandular cells Low Enhanced Q9NYH9 +ENSG00000108651 UTP6 testis cells in seminiferous ducts Medium Enhanced Q9NYH9 +ENSG00000108651 UTP6 testis Leydig cells Medium Enhanced Q9NYH9 +ENSG00000108654 DDX5 epididymis glandular cells High Supported P17844 +ENSG00000108654 DDX5 prostate glandular cells High Supported P17844 +ENSG00000108654 DDX5 seminal vesicle glandular cells Medium Supported P17844 +ENSG00000108654 DDX5 testis cells in seminiferous ducts High Supported P17844 +ENSG00000108654 DDX5 testis Leydig cells High Supported P17844 +ENSG00000108679 LGALS3BP prostate glandular cells High Supported Q08380 +ENSG00000108679 LGALS3BP seminal vesicle glandular cells Medium Supported Q08380 +ENSG00000108679 LGALS3BP testis Leydig cells Low Supported Q08380 +ENSG00000108733 PEX12 epididymis glandular cells Medium Enhanced O00623 +ENSG00000108733 PEX12 prostate glandular cells Medium Enhanced O00623 +ENSG00000108733 PEX12 seminal vesicle glandular cells Medium Enhanced O00623 +ENSG00000108733 PEX12 testis cells in seminiferous ducts Low Enhanced O00623 +ENSG00000108733 PEX12 testis Leydig cells Medium Enhanced O00623 +ENSG00000108784 NAGLU epididymis glandular cells Low Supported P54802 +ENSG00000108784 NAGLU prostate glandular cells Low Supported P54802 +ENSG00000108784 NAGLU seminal vesicle glandular cells Low Supported P54802 +ENSG00000108784 NAGLU testis cells in seminiferous ducts Medium Supported P54802 +ENSG00000108784 NAGLU testis Leydig cells Medium Supported P54802 +ENSG00000108799 EZH1 epididymis glandular cells Medium Supported Q92800 +ENSG00000108799 EZH1 prostate glandular cells Medium Supported Q92800 +ENSG00000108799 EZH1 seminal vesicle glandular cells Low Supported Q92800 +ENSG00000108799 EZH1 testis cells in seminiferous ducts Medium Supported Q92800 +ENSG00000108799 EZH1 testis Leydig cells Medium Supported Q92800 +ENSG00000108829 LRRC59 epididymis glandular cells Medium Enhanced Q96AG4 +ENSG00000108829 LRRC59 prostate glandular cells Medium Enhanced Q96AG4 +ENSG00000108829 LRRC59 seminal vesicle glandular cells High Enhanced Q96AG4 +ENSG00000108829 LRRC59 testis cells in seminiferous ducts Low Enhanced Q96AG4 +ENSG00000108829 LRRC59 testis Leydig cells Medium Enhanced Q96AG4 +ENSG00000108846 ABCC3 prostate glandular cells Low Enhanced O15438 +ENSG00000108846 ABCC3 seminal vesicle glandular cells Medium Enhanced O15438 +ENSG00000108846 ABCC3 testis cells in seminiferous ducts Low Enhanced O15438 +ENSG00000108846 ABCC3 testis Leydig cells Low Enhanced O15438 +ENSG00000108848 LUC7L3 epididymis glandular cells High Enhanced O95232 +ENSG00000108848 LUC7L3 prostate glandular cells High Enhanced O95232 +ENSG00000108848 LUC7L3 seminal vesicle glandular cells High Enhanced O95232 +ENSG00000108848 LUC7L3 testis cells in seminiferous ducts High Enhanced O95232 +ENSG00000108848 LUC7L3 testis Leydig cells High Enhanced O95232 +ENSG00000108854 SMURF2 testis cells in seminiferous ducts Medium Enhanced Q9HAU4 +ENSG00000108854 SMURF2 testis Leydig cells Medium Enhanced Q9HAU4 +ENSG00000108883 EFTUD2 epididymis glandular cells High Supported Q15029 +ENSG00000108883 EFTUD2 prostate glandular cells Medium Supported Q15029 +ENSG00000108883 EFTUD2 seminal vesicle glandular cells High Supported Q15029 +ENSG00000108883 EFTUD2 testis cells in seminiferous ducts High Supported Q15029 +ENSG00000108883 EFTUD2 testis Leydig cells High Supported Q15029 +ENSG00000108984 MAP2K6 epididymis glandular cells Low Enhanced P52564 +ENSG00000108984 MAP2K6 prostate glandular cells Low Enhanced P52564 +ENSG00000108984 MAP2K6 seminal vesicle glandular cells Low Enhanced P52564 +ENSG00000109062 SLC9A3R1 epididymis glandular cells High Enhanced O14745 +ENSG00000109062 SLC9A3R1 prostate glandular cells Low Enhanced O14745 +ENSG00000109062 SLC9A3R1 seminal vesicle glandular cells High Enhanced O14745 +ENSG00000109062 SLC9A3R1 testis cells in seminiferous ducts Low Enhanced O14745 +ENSG00000109062 SLC9A3R1 testis Leydig cells Low Enhanced O14745 +ENSG00000109072 VTN testis Leydig cells Low Supported P04004 +ENSG00000109089 CDR2L prostate glandular cells Medium Enhanced Q86X02 +ENSG00000109089 CDR2L seminal vesicle glandular cells Low Enhanced Q86X02 +ENSG00000109089 CDR2L testis cells in seminiferous ducts Medium Enhanced Q86X02 +ENSG00000109089 CDR2L testis Leydig cells Low Enhanced Q86X02 +ENSG00000109107 ALDOC testis Leydig cells Low Enhanced P09972 +ENSG00000109270 LAMTOR3 epididymis glandular cells High Supported Q9UHA4 +ENSG00000109270 LAMTOR3 prostate glandular cells High Supported Q9UHA4 +ENSG00000109270 LAMTOR3 seminal vesicle glandular cells Medium Supported Q9UHA4 +ENSG00000109270 LAMTOR3 testis cells in seminiferous ducts Low Supported Q9UHA4 +ENSG00000109270 LAMTOR3 testis Leydig cells High Supported Q9UHA4 +ENSG00000109320 NFKB1 epididymis glandular cells Medium Enhanced P19838 +ENSG00000109320 NFKB1 prostate glandular cells Low Enhanced P19838 +ENSG00000109320 NFKB1 seminal vesicle glandular cells Medium Enhanced P19838 +ENSG00000109320 NFKB1 testis cells in seminiferous ducts Medium Enhanced P19838 +ENSG00000109320 NFKB1 testis Leydig cells Low Enhanced P19838 +ENSG00000109381 ELF2 epididymis glandular cells Medium Enhanced Q15723 +ENSG00000109381 ELF2 prostate glandular cells Medium Enhanced Q15723 +ENSG00000109381 ELF2 seminal vesicle glandular cells Medium Enhanced Q15723 +ENSG00000109381 ELF2 testis cells in seminiferous ducts High Enhanced Q15723 +ENSG00000109381 ELF2 testis Leydig cells High Enhanced Q15723 +ENSG00000109458 GAB1 epididymis glandular cells High Enhanced Q13480 +ENSG00000109458 GAB1 prostate glandular cells Medium Enhanced Q13480 +ENSG00000109458 GAB1 seminal vesicle glandular cells Medium Enhanced Q13480 +ENSG00000109458 GAB1 testis cells in seminiferous ducts Medium Enhanced Q13480 +ENSG00000109458 GAB1 testis Leydig cells Low Enhanced Q13480 +ENSG00000109472 CPE prostate glandular cells Medium Supported P16870 +ENSG00000109472 CPE testis cells in seminiferous ducts Low Supported P16870 +ENSG00000109519 GRPEL1 epididymis glandular cells High Supported Q9HAV7 +ENSG00000109519 GRPEL1 prostate glandular cells Medium Supported Q9HAV7 +ENSG00000109519 GRPEL1 seminal vesicle glandular cells High Supported Q9HAV7 +ENSG00000109519 GRPEL1 testis cells in seminiferous ducts High Supported Q9HAV7 +ENSG00000109519 GRPEL1 testis Leydig cells High Supported Q9HAV7 +ENSG00000109534 GAR1 epididymis glandular cells High Supported Q9NY12 +ENSG00000109534 GAR1 prostate glandular cells High Supported Q9NY12 +ENSG00000109534 GAR1 seminal vesicle glandular cells High Supported Q9NY12 +ENSG00000109534 GAR1 testis cells in seminiferous ducts High Supported Q9NY12 +ENSG00000109534 GAR1 testis Leydig cells High Supported Q9NY12 +ENSG00000109576 AADAT testis Leydig cells Low Enhanced Q8N5Z0 +ENSG00000109586 GALNT7 epididymis glandular cells High Enhanced Q86SF2 +ENSG00000109586 GALNT7 prostate glandular cells High Enhanced Q86SF2 +ENSG00000109586 GALNT7 seminal vesicle glandular cells Low Enhanced Q86SF2 +ENSG00000109586 GALNT7 testis cells in seminiferous ducts High Enhanced Q86SF2 +ENSG00000109586 GALNT7 testis Leydig cells High Enhanced Q86SF2 +ENSG00000109610 SOD3 prostate glandular cells Medium Supported P08294 +ENSG00000109610 SOD3 seminal vesicle glandular cells Low Supported P08294 +ENSG00000109610 SOD3 testis cells in seminiferous ducts Medium Supported P08294 +ENSG00000109610 SOD3 testis Leydig cells Low Supported P08294 +ENSG00000109654 TRIM2 testis Leydig cells Low Enhanced Q9C040 +ENSG00000109667 SLC2A9 seminal vesicle glandular cells Low Enhanced Q9NRM0 +ENSG00000109670 FBXW7 epididymis glandular cells Medium Supported Q969H0 +ENSG00000109670 FBXW7 prostate glandular cells High Supported Q969H0 +ENSG00000109670 FBXW7 seminal vesicle glandular cells High Supported Q969H0 +ENSG00000109670 FBXW7 testis cells in seminiferous ducts Medium Supported Q969H0 +ENSG00000109670 FBXW7 testis Leydig cells High Supported Q969H0 +ENSG00000109685 NSD2 epididymis glandular cells Medium Enhanced O96028 +ENSG00000109685 NSD2 prostate glandular cells Low Enhanced O96028 +ENSG00000109685 NSD2 seminal vesicle glandular cells Low Enhanced O96028 +ENSG00000109685 NSD2 testis cells in seminiferous ducts High Enhanced O96028 +ENSG00000109685 NSD2 testis Leydig cells Medium Enhanced O96028 +ENSG00000109686 SH3D19 epididymis glandular cells Medium Enhanced Q5HYK7 +ENSG00000109686 SH3D19 prostate glandular cells Medium Enhanced Q5HYK7 +ENSG00000109686 SH3D19 seminal vesicle glandular cells High Enhanced Q5HYK7 +ENSG00000109686 SH3D19 testis cells in seminiferous ducts Low Enhanced Q5HYK7 +ENSG00000109686 SH3D19 testis Leydig cells Low Enhanced Q5HYK7 +ENSG00000109689 STIM2 epididymis glandular cells High Supported Q9P246 +ENSG00000109689 STIM2 prostate glandular cells Medium Supported Q9P246 +ENSG00000109689 STIM2 seminal vesicle glandular cells Medium Supported Q9P246 +ENSG00000109689 STIM2 testis cells in seminiferous ducts Medium Supported Q9P246 +ENSG00000109689 STIM2 testis Leydig cells Medium Supported Q9P246 +ENSG00000109758 HGFAC testis Leydig cells Low Enhanced Q04756 +ENSG00000109787 KLF3 epididymis glandular cells High Supported P57682 +ENSG00000109787 KLF3 prostate glandular cells High Supported P57682 +ENSG00000109787 KLF3 seminal vesicle glandular cells High Supported P57682 +ENSG00000109787 KLF3 testis cells in seminiferous ducts High Supported P57682 +ENSG00000109787 KLF3 testis Leydig cells High Supported P57682 +ENSG00000109814 UGDH prostate glandular cells High Enhanced O60701 +ENSG00000109814 UGDH seminal vesicle glandular cells Medium Enhanced O60701 +ENSG00000109814 UGDH testis Leydig cells Low Enhanced O60701 +ENSG00000109832 DDX25 seminal vesicle glandular cells Medium Enhanced Q9UHL0 +ENSG00000109832 DDX25 testis elongated or late spermatids High Enhanced Q9UHL0 +ENSG00000109832 DDX25 testis pachytene spermatocytes High Enhanced Q9UHL0 +ENSG00000109832 DDX25 testis preleptotene spermatocytes High Enhanced Q9UHL0 +ENSG00000109832 DDX25 testis round or early spermatids High Enhanced Q9UHL0 +ENSG00000109832 DDX25 testis spermatogonia High Enhanced Q9UHL0 +ENSG00000109846 CRYAB epididymis glandular cells High Enhanced P02511 +ENSG00000109846 CRYAB seminal vesicle glandular cells Medium Enhanced P02511 +ENSG00000109861 CTSC epididymis glandular cells Medium Enhanced P53634 +ENSG00000109861 CTSC seminal vesicle glandular cells Medium Enhanced P53634 +ENSG00000109861 CTSC testis cells in seminiferous ducts Medium Enhanced P53634 +ENSG00000109861 CTSC testis Leydig cells High Enhanced P53634 +ENSG00000109920 FNBP4 epididymis glandular cells Medium Supported Q8N3X1 +ENSG00000109920 FNBP4 seminal vesicle glandular cells Medium Supported Q8N3X1 +ENSG00000109920 FNBP4 testis cells in seminiferous ducts Medium Supported Q8N3X1 +ENSG00000109920 FNBP4 testis Leydig cells Medium Supported Q8N3X1 +ENSG00000109944 C11orf63 testis cells in seminiferous ducts Medium Enhanced Q6NUN7 +ENSG00000109956 B3GAT1 prostate glandular cells Low Enhanced Q9P2W7 +ENSG00000110048 OSBP epididymis glandular cells Medium Enhanced P22059 +ENSG00000110048 OSBP prostate glandular cells Medium Enhanced P22059 +ENSG00000110048 OSBP seminal vesicle glandular cells High Enhanced P22059 +ENSG00000110048 OSBP testis cells in seminiferous ducts High Enhanced P22059 +ENSG00000110048 OSBP testis Leydig cells High Enhanced P22059 +ENSG00000110063 DCPS epididymis glandular cells High Supported Q96C86 +ENSG00000110063 DCPS prostate glandular cells High Supported Q96C86 +ENSG00000110063 DCPS seminal vesicle glandular cells High Supported Q96C86 +ENSG00000110063 DCPS testis cells in seminiferous ducts High Supported Q96C86 +ENSG00000110063 DCPS testis Leydig cells High Supported Q96C86 +ENSG00000110075 PPP6R3 epididymis glandular cells High Enhanced Q5H9R7 +ENSG00000110075 PPP6R3 prostate glandular cells High Enhanced Q5H9R7 +ENSG00000110075 PPP6R3 seminal vesicle glandular cells High Enhanced Q5H9R7 +ENSG00000110075 PPP6R3 testis cells in seminiferous ducts High Enhanced Q5H9R7 +ENSG00000110075 PPP6R3 testis Leydig cells High Enhanced Q5H9R7 +ENSG00000110090 CPT1A epididymis glandular cells Low Enhanced P50416 +ENSG00000110090 CPT1A prostate glandular cells Low Enhanced P50416 +ENSG00000110090 CPT1A seminal vesicle glandular cells Medium Enhanced P50416 +ENSG00000110090 CPT1A testis cells in seminiferous ducts Medium Enhanced P50416 +ENSG00000110090 CPT1A testis Leydig cells High Enhanced P50416 +ENSG00000110104 CCDC86 epididymis glandular cells Medium Enhanced Q9H6F5 +ENSG00000110104 CCDC86 prostate glandular cells Medium Enhanced Q9H6F5 +ENSG00000110104 CCDC86 seminal vesicle glandular cells Medium Enhanced Q9H6F5 +ENSG00000110104 CCDC86 testis cells in seminiferous ducts Medium Enhanced Q9H6F5 +ENSG00000110104 CCDC86 testis Leydig cells Medium Enhanced Q9H6F5 +ENSG00000110107 PRPF19 epididymis glandular cells High Supported Q9UMS4 +ENSG00000110107 PRPF19 prostate glandular cells Medium Supported Q9UMS4 +ENSG00000110107 PRPF19 seminal vesicle glandular cells High Supported Q9UMS4 +ENSG00000110107 PRPF19 testis cells in seminiferous ducts High Supported Q9UMS4 +ENSG00000110107 PRPF19 testis Leydig cells High Supported Q9UMS4 +ENSG00000110330 BIRC2 epididymis glandular cells Medium Supported Q13490 +ENSG00000110330 BIRC2 seminal vesicle glandular cells Medium Supported Q13490 +ENSG00000110330 BIRC2 testis cells in seminiferous ducts Medium Supported Q13490 +ENSG00000110330 BIRC2 testis Leydig cells High Supported Q13490 +ENSG00000110395 CBL epididymis glandular cells Low Enhanced P22681 +ENSG00000110395 CBL testis cells in seminiferous ducts Medium Enhanced P22681 +ENSG00000110435 PDHX epididymis glandular cells Medium Enhanced O00330 +ENSG00000110435 PDHX prostate glandular cells Medium Enhanced O00330 +ENSG00000110435 PDHX seminal vesicle glandular cells Medium Enhanced O00330 +ENSG00000110435 PDHX testis cells in seminiferous ducts Medium Enhanced O00330 +ENSG00000110435 PDHX testis Leydig cells Medium Enhanced O00330 +ENSG00000110619 CARS epididymis glandular cells Medium Enhanced NA +ENSG00000110619 CARS prostate glandular cells Medium Enhanced NA +ENSG00000110619 CARS seminal vesicle glandular cells Medium Enhanced NA +ENSG00000110619 CARS testis cells in seminiferous ducts Medium Enhanced NA +ENSG00000110619 CARS testis Leydig cells Low Enhanced NA +ENSG00000110628 SLC22A18 testis Leydig cells Low Enhanced Q96BI1 +ENSG00000110651 CD81 seminal vesicle glandular cells Low Supported P60033 +ENSG00000110651 CD81 testis cells in seminiferous ducts High Supported P60033 +ENSG00000110693 SOX6 epididymis glandular cells Low Enhanced P35712 +ENSG00000110693 SOX6 testis elongated or late spermatids Low Enhanced P35712 +ENSG00000110693 SOX6 testis round or early spermatids High Enhanced P35712 +ENSG00000110768 GTF2H1 epididymis glandular cells Medium Enhanced P32780 +ENSG00000110768 GTF2H1 prostate glandular cells Medium Enhanced P32780 +ENSG00000110768 GTF2H1 seminal vesicle glandular cells Medium Enhanced P32780 +ENSG00000110768 GTF2H1 testis cells in seminiferous ducts High Enhanced P32780 +ENSG00000110768 GTF2H1 testis Leydig cells Medium Enhanced P32780 +ENSG00000110801 PSMD9 epididymis glandular cells Medium Enhanced O00233 +ENSG00000110801 PSMD9 prostate glandular cells Medium Enhanced O00233 +ENSG00000110801 PSMD9 seminal vesicle glandular cells High Enhanced O00233 +ENSG00000110801 PSMD9 testis cells in seminiferous ducts High Enhanced O00233 +ENSG00000110801 PSMD9 testis Leydig cells Medium Enhanced O00233 +ENSG00000110844 PRPF40B epididymis glandular cells Medium Enhanced Q6NWY9 +ENSG00000110844 PRPF40B prostate glandular cells Medium Enhanced Q6NWY9 +ENSG00000110844 PRPF40B seminal vesicle glandular cells Medium Enhanced Q6NWY9 +ENSG00000110844 PRPF40B testis cells in seminiferous ducts High Enhanced Q6NWY9 +ENSG00000110844 PRPF40B testis Leydig cells Medium Enhanced Q6NWY9 +ENSG00000110888 CAPRIN2 epididymis glandular cells Low Supported Q6IMN6 +ENSG00000110888 CAPRIN2 seminal vesicle glandular cells Low Supported Q6IMN6 +ENSG00000110888 CAPRIN2 testis cells in seminiferous ducts High Supported Q6IMN6 +ENSG00000110888 CAPRIN2 testis Leydig cells Low Supported Q6IMN6 +ENSG00000110955 ATP5B epididymis glandular cells Medium Enhanced P06576 +ENSG00000110955 ATP5B prostate glandular cells Medium Enhanced P06576 +ENSG00000110955 ATP5B seminal vesicle glandular cells Medium Enhanced P06576 +ENSG00000110955 ATP5B testis cells in seminiferous ducts Medium Enhanced P06576 +ENSG00000110955 ATP5B testis Leydig cells Medium Enhanced P06576 +ENSG00000110958 PTGES3 epididymis glandular cells Medium Enhanced Q15185 +ENSG00000110958 PTGES3 prostate glandular cells Medium Enhanced Q15185 +ENSG00000110958 PTGES3 seminal vesicle glandular cells Medium Enhanced Q15185 +ENSG00000110958 PTGES3 testis cells in seminiferous ducts Medium Enhanced Q15185 +ENSG00000111057 KRT18 epididymis glandular cells High Enhanced P05783 +ENSG00000111057 KRT18 prostate glandular cells High Enhanced P05783 +ENSG00000111057 KRT18 seminal vesicle glandular cells High Enhanced P05783 +ENSG00000111142 METAP2 epididymis glandular cells Medium Enhanced P50579 +ENSG00000111142 METAP2 prostate glandular cells Medium Enhanced P50579 +ENSG00000111142 METAP2 seminal vesicle glandular cells High Enhanced P50579 +ENSG00000111142 METAP2 testis cells in seminiferous ducts High Enhanced P50579 +ENSG00000111142 METAP2 testis Leydig cells Medium Enhanced P50579 +ENSG00000111144 LTA4H epididymis glandular cells High Supported P09960 +ENSG00000111144 LTA4H prostate glandular cells High Supported P09960 +ENSG00000111144 LTA4H seminal vesicle glandular cells High Supported P09960 +ENSG00000111144 LTA4H testis cells in seminiferous ducts Medium Supported P09960 +ENSG00000111144 LTA4H testis Leydig cells High Supported P09960 +ENSG00000111254 AKAP3 epididymis glandular cells Medium Enhanced O75969 +ENSG00000111254 AKAP3 testis elongated or late spermatids High Enhanced O75969 +ENSG00000111254 AKAP3 testis pachytene spermatocytes Low Enhanced O75969 +ENSG00000111254 AKAP3 testis preleptotene spermatocytes Low Enhanced O75969 +ENSG00000111254 AKAP3 testis round or early spermatids Low Enhanced O75969 +ENSG00000111254 AKAP3 testis spermatogonia Medium Enhanced O75969 +ENSG00000111319 SCNN1A epididymis glandular cells Medium Enhanced P37088 +ENSG00000111319 SCNN1A prostate glandular cells Medium Enhanced P37088 +ENSG00000111319 SCNN1A seminal vesicle glandular cells Medium Enhanced P37088 +ENSG00000111319 SCNN1A testis cells in seminiferous ducts Medium Enhanced P37088 +ENSG00000111319 SCNN1A testis Leydig cells Medium Enhanced P37088 +ENSG00000111445 RFC5 epididymis glandular cells Medium Supported P40937 +ENSG00000111445 RFC5 seminal vesicle glandular cells Low Supported P40937 +ENSG00000111445 RFC5 testis cells in seminiferous ducts High Supported P40937 +ENSG00000111445 RFC5 testis Leydig cells Low Supported P40937 +ENSG00000111602 TIMELESS seminal vesicle glandular cells Low Enhanced Q9UNS1 +ENSG00000111602 TIMELESS testis cells in seminiferous ducts Medium Enhanced Q9UNS1 +ENSG00000111605 CPSF6 epididymis glandular cells High Supported Q16630 +ENSG00000111605 CPSF6 prostate glandular cells High Supported Q16630 +ENSG00000111605 CPSF6 seminal vesicle glandular cells High Supported Q16630 +ENSG00000111605 CPSF6 testis cells in seminiferous ducts High Supported Q16630 +ENSG00000111605 CPSF6 testis Leydig cells High Supported Q16630 +ENSG00000111640 GAPDH epididymis glandular cells High Supported P04406 +ENSG00000111640 GAPDH prostate glandular cells Medium Supported P04406 +ENSG00000111640 GAPDH seminal vesicle glandular cells Medium Supported P04406 +ENSG00000111640 GAPDH testis cells in seminiferous ducts Medium Supported P04406 +ENSG00000111640 GAPDH testis Leydig cells High Supported P04406 +ENSG00000111641 NOP2 prostate glandular cells Low Supported P46087 +ENSG00000111641 NOP2 testis cells in seminiferous ducts Low Supported P46087 +ENSG00000111641 NOP2 testis Leydig cells Medium Supported P46087 +ENSG00000111642 CHD4 epididymis glandular cells Medium Supported Q14839 +ENSG00000111642 CHD4 prostate glandular cells Low Supported Q14839 +ENSG00000111642 CHD4 seminal vesicle glandular cells Medium Supported Q14839 +ENSG00000111642 CHD4 testis cells in seminiferous ducts High Supported Q14839 +ENSG00000111642 CHD4 testis Leydig cells Medium Supported Q14839 +ENSG00000111644 ACRBP testis elongated or late spermatids High Enhanced Q8NEB7 +ENSG00000111644 ACRBP testis Leydig cells Low Enhanced Q8NEB7 +ENSG00000111644 ACRBP testis pachytene spermatocytes Medium Enhanced Q8NEB7 +ENSG00000111644 ACRBP testis preleptotene spermatocytes Medium Enhanced Q8NEB7 +ENSG00000111644 ACRBP testis round or early spermatids High Enhanced Q8NEB7 +ENSG00000111644 ACRBP testis spermatogonia Medium Enhanced Q8NEB7 +ENSG00000111652 COPS7A epididymis glandular cells Medium Supported Q9UBW8 +ENSG00000111652 COPS7A prostate glandular cells Medium Supported Q9UBW8 +ENSG00000111652 COPS7A seminal vesicle glandular cells Medium Supported Q9UBW8 +ENSG00000111652 COPS7A testis cells in seminiferous ducts Medium Supported Q9UBW8 +ENSG00000111652 COPS7A testis Leydig cells Medium Supported Q9UBW8 +ENSG00000111676 ATN1 epididymis glandular cells Medium Enhanced P54259 +ENSG00000111676 ATN1 prostate glandular cells Low Enhanced P54259 +ENSG00000111676 ATN1 seminal vesicle glandular cells Medium Enhanced P54259 +ENSG00000111676 ATN1 testis Leydig cells Medium Enhanced P54259 +ENSG00000111716 LDHB epididymis glandular cells High Enhanced P07195 +ENSG00000111716 LDHB prostate glandular cells Medium Enhanced P07195 +ENSG00000111716 LDHB seminal vesicle glandular cells High Enhanced P07195 +ENSG00000111716 LDHB testis cells in seminiferous ducts Medium Enhanced P07195 +ENSG00000111716 LDHB testis Leydig cells Medium Enhanced P07195 +ENSG00000111725 PRKAB1 epididymis glandular cells Medium Enhanced Q9Y478 +ENSG00000111725 PRKAB1 prostate glandular cells Medium Enhanced Q9Y478 +ENSG00000111725 PRKAB1 seminal vesicle glandular cells Medium Enhanced Q9Y478 +ENSG00000111725 PRKAB1 testis cells in seminiferous ducts Medium Enhanced Q9Y478 +ENSG00000111725 PRKAB1 testis Leydig cells Medium Enhanced Q9Y478 +ENSG00000111726 CMAS epididymis glandular cells High Supported Q8NFW8 +ENSG00000111726 CMAS prostate glandular cells High Supported Q8NFW8 +ENSG00000111726 CMAS seminal vesicle glandular cells High Supported Q8NFW8 +ENSG00000111726 CMAS testis cells in seminiferous ducts High Supported Q8NFW8 +ENSG00000111726 CMAS testis Leydig cells High Supported Q8NFW8 +ENSG00000111783 RFX4 testis pachytene spermatocytes High Enhanced Q33E94 +ENSG00000111783 RFX4 testis peritubular cells High Enhanced Q33E94 +ENSG00000111783 RFX4 testis preleptotene spermatocytes Low Enhanced Q33E94 +ENSG00000111783 RFX4 testis round or early spermatids High Enhanced Q33E94 +ENSG00000111786 SRSF9 epididymis glandular cells High Enhanced Q13242 +ENSG00000111786 SRSF9 prostate glandular cells Medium Enhanced Q13242 +ENSG00000111786 SRSF9 seminal vesicle glandular cells Medium Enhanced Q13242 +ENSG00000111786 SRSF9 testis cells in seminiferous ducts High Enhanced Q13242 +ENSG00000111786 SRSF9 testis Leydig cells High Enhanced Q13242 +ENSG00000111790 FGFR1OP2 epididymis glandular cells High Supported Q9NVK5 +ENSG00000111790 FGFR1OP2 prostate glandular cells High Supported Q9NVK5 +ENSG00000111790 FGFR1OP2 seminal vesicle glandular cells High Supported Q9NVK5 +ENSG00000111790 FGFR1OP2 testis cells in seminiferous ducts High Supported Q9NVK5 +ENSG00000111790 FGFR1OP2 testis Leydig cells High Supported Q9NVK5 +ENSG00000111801 BTN3A3 epididymis glandular cells Medium Enhanced O00478 +ENSG00000111801 BTN3A3 prostate glandular cells Medium Enhanced O00478 +ENSG00000111801 BTN3A3 seminal vesicle glandular cells Medium Enhanced O00478 +ENSG00000111801 BTN3A3 testis cells in seminiferous ducts Medium Enhanced O00478 +ENSG00000111801 BTN3A3 testis Leydig cells Medium Enhanced O00478 +ENSG00000111802 TDP2 epididymis glandular cells Low Enhanced O95551 +ENSG00000111802 TDP2 prostate glandular cells Medium Enhanced O95551 +ENSG00000111802 TDP2 testis cells in seminiferous ducts Medium Enhanced O95551 +ENSG00000111802 TDP2 testis Leydig cells Low Enhanced O95551 +ENSG00000111834 RSPH4A epididymis glandular cells Medium Enhanced Q5TD94 +ENSG00000111845 PAK1IP1 epididymis glandular cells High Supported Q9NWT1 +ENSG00000111845 PAK1IP1 prostate glandular cells High Supported Q9NWT1 +ENSG00000111845 PAK1IP1 seminal vesicle glandular cells High Supported Q9NWT1 +ENSG00000111845 PAK1IP1 testis cells in seminiferous ducts Medium Supported Q9NWT1 +ENSG00000111845 PAK1IP1 testis Leydig cells Medium Supported Q9NWT1 +ENSG00000111907 TPD52L1 epididymis glandular cells High Enhanced Q16890 +ENSG00000111907 TPD52L1 prostate glandular cells High Enhanced Q16890 +ENSG00000111907 TPD52L1 seminal vesicle glandular cells High Enhanced Q16890 +ENSG00000111907 TPD52L1 testis cells in seminiferous ducts Low Enhanced Q16890 +ENSG00000111907 TPD52L1 testis Leydig cells Low Enhanced Q16890 +ENSG00000111981 ULBP1 testis elongated or late spermatids High Enhanced Q9BZM6 +ENSG00000111981 ULBP1 testis Leydig cells Low Enhanced Q9BZM6 +ENSG00000111981 ULBP1 testis sertoli cells High Enhanced Q9BZM6 +ENSG00000112038 OPRM1 testis elongated or late spermatids High Enhanced P35372 +ENSG00000112038 OPRM1 testis round or early spermatids Medium Enhanced P35372 +ENSG00000112038 OPRM1 testis sertoli cells High Enhanced P35372 +ENSG00000112039 FANCE epididymis glandular cells Medium Enhanced Q9HB96 +ENSG00000112039 FANCE prostate glandular cells Medium Enhanced Q9HB96 +ENSG00000112039 FANCE seminal vesicle glandular cells Medium Enhanced Q9HB96 +ENSG00000112039 FANCE testis cells in seminiferous ducts High Enhanced Q9HB96 +ENSG00000112039 FANCE testis Leydig cells High Enhanced Q9HB96 +ENSG00000112053 SLC26A8 testis cells in seminiferous ducts Medium Enhanced Q96RN1 +ENSG00000112081 SRSF3 epididymis glandular cells High Supported P84103 +ENSG00000112081 SRSF3 prostate glandular cells High Supported P84103 +ENSG00000112081 SRSF3 seminal vesicle glandular cells High Supported P84103 +ENSG00000112081 SRSF3 testis cells in seminiferous ducts High Supported P84103 +ENSG00000112081 SRSF3 testis Leydig cells High Supported P84103 +ENSG00000112096 SOD2 epididymis glandular cells Medium Supported P04179 +ENSG00000112096 SOD2 prostate glandular cells Medium Supported P04179 +ENSG00000112096 SOD2 seminal vesicle glandular cells Medium Supported P04179 +ENSG00000112096 SOD2 testis cells in seminiferous ducts Medium Supported P04179 +ENSG00000112096 SOD2 testis Leydig cells Medium Supported P04179 +ENSG00000112110 MRPL18 epididymis glandular cells Low Enhanced Q9H0U6 +ENSG00000112110 MRPL18 prostate glandular cells Low Enhanced Q9H0U6 +ENSG00000112110 MRPL18 seminal vesicle glandular cells Medium Enhanced Q9H0U6 +ENSG00000112110 MRPL18 testis cells in seminiferous ducts Medium Enhanced Q9H0U6 +ENSG00000112110 MRPL18 testis Leydig cells Medium Enhanced Q9H0U6 +ENSG00000112118 MCM3 testis cells in seminiferous ducts Medium Supported P25205 +ENSG00000112137 PHACTR1 epididymis glandular cells Low Enhanced H0Y3U1 +ENSG00000112137 PHACTR1 testis cells in seminiferous ducts Low Enhanced H0Y3U1 +ENSG00000112137 PHACTR1 testis Leydig cells Low Enhanced H0Y3U1 +ENSG00000112182 BACH2 epididymis glandular cells Low Enhanced Q9BYV9 +ENSG00000112182 BACH2 testis cells in seminiferous ducts Medium Enhanced Q9BYV9 +ENSG00000112182 BACH2 testis Leydig cells Medium Enhanced Q9BYV9 +ENSG00000112183 RBM24 testis cells in seminiferous ducts Low Enhanced Q9BX46 +ENSG00000112208 BAG2 prostate glandular cells Low Enhanced O95816 +ENSG00000112208 BAG2 testis cells in seminiferous ducts Medium Enhanced O95816 +ENSG00000112208 BAG2 testis Leydig cells Medium Enhanced O95816 +ENSG00000112210 RAB23 epididymis glandular cells Medium Enhanced Q9ULC3 +ENSG00000112210 RAB23 prostate glandular cells Medium Enhanced Q9ULC3 +ENSG00000112210 RAB23 seminal vesicle glandular cells Medium Enhanced Q9ULC3 +ENSG00000112210 RAB23 testis cells in seminiferous ducts Medium Enhanced Q9ULC3 +ENSG00000112210 RAB23 testis Leydig cells Medium Enhanced Q9ULC3 +ENSG00000112232 KHDRBS2 epididymis glandular cells High Supported Q5VWX1 +ENSG00000112232 KHDRBS2 prostate glandular cells High Supported Q5VWX1 +ENSG00000112232 KHDRBS2 testis cells in seminiferous ducts High Supported Q5VWX1 +ENSG00000112232 KHDRBS2 testis Leydig cells Medium Supported Q5VWX1 +ENSG00000112249 ASCC3 epididymis glandular cells High Enhanced Q8N3C0 +ENSG00000112249 ASCC3 prostate glandular cells Medium Enhanced Q8N3C0 +ENSG00000112249 ASCC3 seminal vesicle glandular cells Medium Enhanced Q8N3C0 +ENSG00000112249 ASCC3 testis cells in seminiferous ducts Medium Enhanced Q8N3C0 +ENSG00000112249 ASCC3 testis Leydig cells Medium Enhanced Q8N3C0 +ENSG00000112273 HDGFL1 testis pachytene spermatocytes High Enhanced Q5TGJ6 +ENSG00000112273 HDGFL1 testis preleptotene spermatocytes Medium Enhanced Q5TGJ6 +ENSG00000112273 HDGFL1 testis round or early spermatids High Enhanced Q5TGJ6 +ENSG00000112276 BVES epididymis glandular cells Low Enhanced Q8NE79 +ENSG00000112276 BVES prostate glandular cells Low Enhanced Q8NE79 +ENSG00000112276 BVES testis cells in seminiferous ducts Low Enhanced Q8NE79 +ENSG00000112276 BVES testis Leydig cells Low Enhanced Q8NE79 +ENSG00000112294 ALDH5A1 epididymis glandular cells Low Enhanced P51649 +ENSG00000112294 ALDH5A1 prostate glandular cells Medium Enhanced P51649 +ENSG00000112294 ALDH5A1 seminal vesicle glandular cells Medium Enhanced P51649 +ENSG00000112294 ALDH5A1 testis cells in seminiferous ducts Medium Enhanced P51649 +ENSG00000112294 ALDH5A1 testis Leydig cells Medium Enhanced P51649 +ENSG00000112308 C6orf62 epididymis glandular cells Medium Enhanced Q9GZU0 +ENSG00000112308 C6orf62 prostate glandular cells Medium Enhanced Q9GZU0 +ENSG00000112308 C6orf62 seminal vesicle glandular cells Medium Enhanced Q9GZU0 +ENSG00000112308 C6orf62 testis cells in seminiferous ducts Medium Enhanced Q9GZU0 +ENSG00000112308 C6orf62 testis Leydig cells High Enhanced Q9GZU0 +ENSG00000112312 GMNN testis cells in seminiferous ducts High Enhanced O75496 +ENSG00000112319 EYA4 epididymis glandular cells Low Enhanced O95677 +ENSG00000112319 EYA4 prostate glandular cells Medium Enhanced O95677 +ENSG00000112319 EYA4 seminal vesicle glandular cells Medium Enhanced O95677 +ENSG00000112319 EYA4 testis cells in seminiferous ducts Low Enhanced O95677 +ENSG00000112319 EYA4 testis Leydig cells Medium Enhanced O95677 +ENSG00000112333 NR2E1 testis Leydig cells Low Enhanced Q9Y466 +ENSG00000112530 PACRG testis elongated or late spermatids High Enhanced Q96M98 +ENSG00000112530 PACRG testis round or early spermatids Low Enhanced Q96M98 +ENSG00000112531 QKI epididymis glandular cells Low Enhanced Q96PU8 +ENSG00000112531 QKI prostate glandular cells Low Enhanced Q96PU8 +ENSG00000112531 QKI testis cells in seminiferous ducts Medium Enhanced Q96PU8 +ENSG00000112531 QKI testis Leydig cells Low Enhanced Q96PU8 +ENSG00000112541 PDE10A testis Leydig cells Low Supported Q9Y233 +ENSG00000112578 BYSL epididymis glandular cells High Enhanced Q13895 +ENSG00000112578 BYSL prostate glandular cells Medium Enhanced Q13895 +ENSG00000112578 BYSL seminal vesicle glandular cells Medium Enhanced Q13895 +ENSG00000112578 BYSL testis cells in seminiferous ducts Low Enhanced Q13895 +ENSG00000112578 BYSL testis Leydig cells Medium Enhanced Q13895 +ENSG00000112658 SRF epididymis glandular cells Low Supported P11831 +ENSG00000112658 SRF prostate glandular cells Medium Supported P11831 +ENSG00000112658 SRF testis cells in seminiferous ducts High Supported P11831 +ENSG00000112658 SRF testis Leydig cells Medium Supported P11831 +ENSG00000112667 DNPH1 epididymis glandular cells Medium Enhanced O43598 +ENSG00000112667 DNPH1 prostate glandular cells Low Enhanced O43598 +ENSG00000112667 DNPH1 seminal vesicle glandular cells Medium Enhanced O43598 +ENSG00000112667 DNPH1 testis cells in seminiferous ducts Low Enhanced O43598 +ENSG00000112667 DNPH1 testis Leydig cells Medium Enhanced O43598 +ENSG00000112699 GMDS epididymis glandular cells Medium Enhanced O60547 +ENSG00000112699 GMDS prostate glandular cells Medium Enhanced O60547 +ENSG00000112699 GMDS seminal vesicle glandular cells Medium Enhanced O60547 +ENSG00000112699 GMDS testis cells in seminiferous ducts Medium Enhanced O60547 +ENSG00000112699 GMDS testis Leydig cells Medium Enhanced O60547 +ENSG00000112715 VEGFA epididymis glandular cells Medium Supported P15692 +ENSG00000112715 VEGFA prostate glandular cells High Supported P15692 +ENSG00000112715 VEGFA seminal vesicle glandular cells High Supported P15692 +ENSG00000112715 VEGFA testis cells in seminiferous ducts Medium Supported P15692 +ENSG00000112715 VEGFA testis Leydig cells High Supported P15692 +ENSG00000112742 TTK epididymis glandular cells High Enhanced P33981 +ENSG00000112742 TTK prostate glandular cells Medium Enhanced P33981 +ENSG00000112742 TTK seminal vesicle glandular cells Medium Enhanced P33981 +ENSG00000112742 TTK testis cells in seminiferous ducts High Enhanced P33981 +ENSG00000112742 TTK testis Leydig cells Medium Enhanced P33981 +ENSG00000112796 ENPP5 epididymis glandular cells High Enhanced Q9UJA9 +ENSG00000112796 ENPP5 prostate glandular cells Medium Enhanced Q9UJA9 +ENSG00000112796 ENPP5 seminal vesicle glandular cells Medium Enhanced Q9UJA9 +ENSG00000112796 ENPP5 testis cells in seminiferous ducts High Enhanced Q9UJA9 +ENSG00000112796 ENPP5 testis Leydig cells Medium Enhanced Q9UJA9 +ENSG00000112852 PCDHB2 testis cells in seminiferous ducts Low Enhanced Q9Y5E7 +ENSG00000112852 PCDHB2 testis Leydig cells Low Enhanced Q9Y5E7 +ENSG00000112874 NUDT12 epididymis glandular cells Medium Supported Q9BQG2 +ENSG00000112874 NUDT12 prostate glandular cells Medium Supported Q9BQG2 +ENSG00000112874 NUDT12 seminal vesicle glandular cells Medium Supported Q9BQG2 +ENSG00000112874 NUDT12 testis cells in seminiferous ducts High Supported Q9BQG2 +ENSG00000112874 NUDT12 testis Leydig cells High Supported Q9BQG2 +ENSG00000112893 MAN2A1 epididymis glandular cells Low Enhanced Q16706 +ENSG00000112893 MAN2A1 prostate glandular cells Low Enhanced Q16706 +ENSG00000112893 MAN2A1 seminal vesicle glandular cells Low Enhanced Q16706 +ENSG00000112893 MAN2A1 testis cells in seminiferous ducts Low Enhanced Q16706 +ENSG00000112893 MAN2A1 testis Leydig cells Low Enhanced Q16706 +ENSG00000112941 PAPD7 epididymis glandular cells High Enhanced Q5XG87 +ENSG00000112941 PAPD7 prostate glandular cells High Enhanced Q5XG87 +ENSG00000112941 PAPD7 seminal vesicle glandular cells High Enhanced Q5XG87 +ENSG00000112941 PAPD7 testis cells in seminiferous ducts High Enhanced Q5XG87 +ENSG00000112941 PAPD7 testis Leydig cells High Enhanced Q5XG87 +ENSG00000112964 GHR epididymis glandular cells Medium Enhanced P10912 +ENSG00000112964 GHR testis cells in seminiferous ducts Low Enhanced P10912 +ENSG00000112964 GHR testis Leydig cells Medium Enhanced P10912 +ENSG00000112983 BRD8 epididymis glandular cells Medium Supported Q9H0E9 +ENSG00000112983 BRD8 prostate glandular cells Medium Supported Q9H0E9 +ENSG00000112983 BRD8 seminal vesicle glandular cells Medium Supported Q9H0E9 +ENSG00000112983 BRD8 testis cells in seminiferous ducts High Supported Q9H0E9 +ENSG00000112983 BRD8 testis Leydig cells Low Supported Q9H0E9 +ENSG00000112992 NNT epididymis glandular cells Medium Enhanced Q13423 +ENSG00000112992 NNT seminal vesicle glandular cells High Enhanced Q13423 +ENSG00000112992 NNT testis Leydig cells High Enhanced Q13423 +ENSG00000112996 MRPS30 epididymis glandular cells High Enhanced Q9NP92 +ENSG00000112996 MRPS30 prostate glandular cells Medium Enhanced Q9NP92 +ENSG00000112996 MRPS30 seminal vesicle glandular cells Medium Enhanced Q9NP92 +ENSG00000112996 MRPS30 testis cells in seminiferous ducts Medium Enhanced Q9NP92 +ENSG00000112996 MRPS30 testis Leydig cells Medium Enhanced Q9NP92 +ENSG00000113013 HSPA9 epididymis glandular cells High Enhanced P38646 +ENSG00000113013 HSPA9 prostate glandular cells High Enhanced P38646 +ENSG00000113013 HSPA9 seminal vesicle glandular cells High Enhanced P38646 +ENSG00000113013 HSPA9 testis cells in seminiferous ducts High Enhanced P38646 +ENSG00000113013 HSPA9 testis Leydig cells High Enhanced P38646 +ENSG00000113140 SPARC testis cells in seminiferous ducts High Supported P09486 +ENSG00000113140 SPARC testis Leydig cells High Supported P09486 +ENSG00000113141 IK epididymis glandular cells High Supported Q13123 +ENSG00000113141 IK prostate glandular cells Medium Supported Q13123 +ENSG00000113141 IK seminal vesicle glandular cells Medium Supported Q13123 +ENSG00000113141 IK testis cells in seminiferous ducts High Supported Q13123 +ENSG00000113141 IK testis Leydig cells High Supported Q13123 +ENSG00000113273 ARSB epididymis glandular cells Medium Enhanced P15848 +ENSG00000113273 ARSB prostate glandular cells Medium Enhanced P15848 +ENSG00000113273 ARSB seminal vesicle glandular cells Medium Enhanced P15848 +ENSG00000113273 ARSB testis cells in seminiferous ducts Medium Enhanced P15848 +ENSG00000113273 ARSB testis Leydig cells Medium Enhanced P15848 +ENSG00000113282 CLINT1 epididymis glandular cells High Supported Q14677 +ENSG00000113282 CLINT1 prostate glandular cells Medium Supported Q14677 +ENSG00000113282 CLINT1 seminal vesicle glandular cells High Supported Q14677 +ENSG00000113282 CLINT1 testis cells in seminiferous ducts Medium Supported Q14677 +ENSG00000113282 CLINT1 testis Leydig cells Medium Supported Q14677 +ENSG00000113328 CCNG1 epididymis glandular cells High Supported P51959 +ENSG00000113328 CCNG1 prostate glandular cells Medium Supported P51959 +ENSG00000113328 CCNG1 seminal vesicle glandular cells Medium Supported P51959 +ENSG00000113328 CCNG1 testis cells in seminiferous ducts High Supported P51959 +ENSG00000113356 POLR3G testis cells in seminiferous ducts High Enhanced O15318 +ENSG00000113361 CDH6 epididymis glandular cells Low Enhanced P55285 +ENSG00000113361 CDH6 prostate glandular cells Low Enhanced P55285 +ENSG00000113361 CDH6 testis Leydig cells Low Enhanced P55285 +ENSG00000113368 LMNB1 epididymis glandular cells High Supported P20700 +ENSG00000113368 LMNB1 prostate glandular cells High Supported P20700 +ENSG00000113368 LMNB1 seminal vesicle glandular cells High Supported P20700 +ENSG00000113368 LMNB1 testis cells in seminiferous ducts High Supported P20700 +ENSG00000113368 LMNB1 testis Leydig cells High Supported P20700 +ENSG00000113387 SUB1 epididymis glandular cells Medium Supported P53999 +ENSG00000113387 SUB1 prostate glandular cells High Supported P53999 +ENSG00000113387 SUB1 seminal vesicle glandular cells Medium Supported P53999 +ENSG00000113387 SUB1 testis cells in seminiferous ducts Medium Supported P53999 +ENSG00000113387 SUB1 testis Leydig cells Medium Supported P53999 +ENSG00000113522 RAD50 epididymis glandular cells High Enhanced Q92878 +ENSG00000113522 RAD50 prostate glandular cells High Enhanced Q92878 +ENSG00000113522 RAD50 seminal vesicle glandular cells Medium Enhanced Q92878 +ENSG00000113522 RAD50 testis cells in seminiferous ducts High Enhanced Q92878 +ENSG00000113522 RAD50 testis Leydig cells High Enhanced Q92878 +ENSG00000113569 NUP155 epididymis glandular cells Medium Enhanced O75694 +ENSG00000113569 NUP155 prostate glandular cells Low Enhanced O75694 +ENSG00000113569 NUP155 seminal vesicle glandular cells Low Enhanced O75694 +ENSG00000113569 NUP155 testis cells in seminiferous ducts Medium Enhanced O75694 +ENSG00000113569 NUP155 testis Leydig cells Medium Enhanced O75694 +ENSG00000113580 NR3C1 epididymis glandular cells High Supported P04150 +ENSG00000113580 NR3C1 prostate glandular cells High Supported P04150 +ENSG00000113580 NR3C1 seminal vesicle glandular cells High Supported P04150 +ENSG00000113580 NR3C1 testis cells in seminiferous ducts Medium Supported P04150 +ENSG00000113580 NR3C1 testis Leydig cells High Supported P04150 +ENSG00000113593 PPWD1 epididymis glandular cells Medium Enhanced Q96BP3 +ENSG00000113593 PPWD1 prostate glandular cells Medium Enhanced Q96BP3 +ENSG00000113593 PPWD1 seminal vesicle glandular cells Low Enhanced Q96BP3 +ENSG00000113593 PPWD1 testis cells in seminiferous ducts Medium Enhanced Q96BP3 +ENSG00000113593 PPWD1 testis Leydig cells Medium Enhanced Q96BP3 +ENSG00000113648 H2AFY epididymis glandular cells Medium Supported O75367 +ENSG00000113648 H2AFY prostate glandular cells Low Supported O75367 +ENSG00000113648 H2AFY seminal vesicle glandular cells Medium Supported O75367 +ENSG00000113648 H2AFY testis cells in seminiferous ducts High Supported O75367 +ENSG00000113648 H2AFY testis Leydig cells Low Supported O75367 +ENSG00000113649 TCERG1 epididymis glandular cells Medium Enhanced O14776 +ENSG00000113649 TCERG1 prostate glandular cells Low Enhanced O14776 +ENSG00000113649 TCERG1 seminal vesicle glandular cells Medium Enhanced O14776 +ENSG00000113649 TCERG1 testis cells in seminiferous ducts Medium Enhanced O14776 +ENSG00000113649 TCERG1 testis Leydig cells Medium Enhanced O14776 +ENSG00000113719 ERGIC1 epididymis glandular cells High Enhanced Q969X5 +ENSG00000113719 ERGIC1 prostate glandular cells High Enhanced Q969X5 +ENSG00000113719 ERGIC1 seminal vesicle glandular cells High Enhanced Q969X5 +ENSG00000113719 ERGIC1 testis cells in seminiferous ducts Medium Enhanced Q969X5 +ENSG00000113719 ERGIC1 testis Leydig cells High Enhanced Q969X5 +ENSG00000113721 PDGFRB epididymis glandular cells Low Enhanced P09619 +ENSG00000113721 PDGFRB prostate glandular cells Low Enhanced P09619 +ENSG00000113721 PDGFRB testis cells in seminiferous ducts Medium Enhanced P09619 +ENSG00000113734 BNIP1 epididymis glandular cells Medium Enhanced Q12981 +ENSG00000113734 BNIP1 prostate glandular cells Medium Enhanced Q12981 +ENSG00000113734 BNIP1 seminal vesicle glandular cells Low Enhanced Q12981 +ENSG00000113734 BNIP1 testis cells in seminiferous ducts Medium Enhanced Q12981 +ENSG00000113734 BNIP1 testis Leydig cells Medium Enhanced Q12981 +ENSG00000113758 DBN1 epididymis glandular cells Medium Enhanced Q16643 +ENSG00000113758 DBN1 prostate glandular cells Low Enhanced Q16643 +ENSG00000113758 DBN1 testis cells in seminiferous ducts Medium Enhanced Q16643 +ENSG00000113916 BCL6 epididymis glandular cells Low Enhanced P41182 +ENSG00000113916 BCL6 testis cells in seminiferous ducts High Enhanced P41182 +ENSG00000113916 BCL6 testis Leydig cells Low Enhanced P41182 +ENSG00000113924 HGD epididymis glandular cells Low Enhanced Q93099 +ENSG00000113924 HGD prostate glandular cells Medium Enhanced Q93099 +ENSG00000114030 KPNA1 epididymis glandular cells Medium Enhanced P52294 +ENSG00000114030 KPNA1 seminal vesicle glandular cells Medium Enhanced P52294 +ENSG00000114030 KPNA1 testis cells in seminiferous ducts High Enhanced P52294 +ENSG00000114030 KPNA1 testis Leydig cells High Enhanced P52294 +ENSG00000114054 PCCB epididymis glandular cells Medium Enhanced P05166 +ENSG00000114054 PCCB prostate glandular cells High Enhanced P05166 +ENSG00000114054 PCCB seminal vesicle glandular cells Medium Enhanced P05166 +ENSG00000114054 PCCB testis cells in seminiferous ducts Medium Enhanced P05166 +ENSG00000114054 PCCB testis Leydig cells High Enhanced P05166 +ENSG00000114107 CEP70 epididymis glandular cells Medium Enhanced Q8NHQ1 +ENSG00000114107 CEP70 prostate glandular cells Medium Enhanced Q8NHQ1 +ENSG00000114107 CEP70 seminal vesicle glandular cells Medium Enhanced Q8NHQ1 +ENSG00000114107 CEP70 testis cells in seminiferous ducts High Enhanced Q8NHQ1 +ENSG00000114107 CEP70 testis Leydig cells Medium Enhanced Q8NHQ1 +ENSG00000114115 RBP1 testis cells in seminiferous ducts Low Enhanced P09455 +ENSG00000114115 RBP1 testis Leydig cells High Enhanced P09455 +ENSG00000114126 TFDP2 epididymis glandular cells High Supported Q14188 +ENSG00000114126 TFDP2 prostate glandular cells Medium Supported Q14188 +ENSG00000114126 TFDP2 seminal vesicle glandular cells High Supported Q14188 +ENSG00000114126 TFDP2 testis cells in seminiferous ducts High Supported Q14188 +ENSG00000114126 TFDP2 testis Leydig cells High Supported Q14188 +ENSG00000114166 KAT2B epididymis glandular cells Medium Supported Q92831 +ENSG00000114166 KAT2B prostate glandular cells Medium Supported Q92831 +ENSG00000114166 KAT2B seminal vesicle glandular cells Low Supported Q92831 +ENSG00000114166 KAT2B testis Leydig cells Low Supported Q92831 +ENSG00000114331 ACAP2 epididymis glandular cells High Supported Q15057 +ENSG00000114331 ACAP2 prostate glandular cells High Supported Q15057 +ENSG00000114331 ACAP2 seminal vesicle glandular cells Medium Supported Q15057 +ENSG00000114331 ACAP2 testis cells in seminiferous ducts High Supported Q15057 +ENSG00000114331 ACAP2 testis Leydig cells Medium Supported Q15057 +ENSG00000114439 BBX epididymis glandular cells High Enhanced Q8WY36 +ENSG00000114439 BBX prostate glandular cells Medium Enhanced Q8WY36 +ENSG00000114439 BBX seminal vesicle glandular cells Medium Enhanced Q8WY36 +ENSG00000114439 BBX testis cells in seminiferous ducts Medium Enhanced Q8WY36 +ENSG00000114439 BBX testis Leydig cells Medium Enhanced Q8WY36 +ENSG00000114446 IFT57 epididymis glandular cells Medium Supported Q9NWB7 +ENSG00000114446 IFT57 prostate glandular cells Medium Supported Q9NWB7 +ENSG00000114446 IFT57 seminal vesicle glandular cells High Supported Q9NWB7 +ENSG00000114446 IFT57 testis cells in seminiferous ducts High Supported Q9NWB7 +ENSG00000114446 IFT57 testis Leydig cells Medium Supported Q9NWB7 +ENSG00000114450 GNB4 epididymis glandular cells Medium Enhanced Q9HAV0 +ENSG00000114450 GNB4 prostate glandular cells Medium Enhanced Q9HAV0 +ENSG00000114450 GNB4 seminal vesicle glandular cells Medium Enhanced Q9HAV0 +ENSG00000114450 GNB4 testis cells in seminiferous ducts Medium Enhanced Q9HAV0 +ENSG00000114450 GNB4 testis Leydig cells Low Enhanced Q9HAV0 +ENSG00000114473 IQCG testis cells in seminiferous ducts Low Enhanced Q9H095 +ENSG00000114473 IQCG testis Leydig cells Low Enhanced Q9H095 +ENSG00000114480 GBE1 epididymis glandular cells Medium Enhanced Q04446 +ENSG00000114480 GBE1 prostate glandular cells Medium Enhanced Q04446 +ENSG00000114480 GBE1 seminal vesicle glandular cells Medium Enhanced Q04446 +ENSG00000114480 GBE1 testis cells in seminiferous ducts Medium Enhanced Q04446 +ENSG00000114480 GBE1 testis Leydig cells High Enhanced Q04446 +ENSG00000114487 MORC1 testis Leydig cells Low Supported Q86VD1 +ENSG00000114487 MORC1 testis pachytene spermatocytes High Supported Q86VD1 +ENSG00000114487 MORC1 testis preleptotene spermatocytes High Supported Q86VD1 +ENSG00000114487 MORC1 testis round or early spermatids High Supported Q86VD1 +ENSG00000114487 MORC1 testis spermatogonia Medium Supported Q86VD1 +ENSG00000114503 NCBP2 epididymis glandular cells High Supported P52298 +ENSG00000114503 NCBP2 prostate glandular cells Medium Supported P52298 +ENSG00000114503 NCBP2 seminal vesicle glandular cells Medium Supported P52298 +ENSG00000114503 NCBP2 testis cells in seminiferous ducts High Supported P52298 +ENSG00000114503 NCBP2 testis Leydig cells High Supported P52298 +ENSG00000114547 ROPN1B epididymis glandular cells Low Supported Q9BZX4 +ENSG00000114547 ROPN1B testis cells in seminiferous ducts Medium Supported Q9BZX4 +ENSG00000114638 UPK1B testis cells in seminiferous ducts Low Enhanced O75841 +ENSG00000114745 GORASP1 epididymis glandular cells High Enhanced Q9BQQ3 +ENSG00000114745 GORASP1 prostate glandular cells Low Enhanced Q9BQQ3 +ENSG00000114745 GORASP1 seminal vesicle glandular cells Medium Enhanced Q9BQQ3 +ENSG00000114745 GORASP1 testis cells in seminiferous ducts Medium Enhanced Q9BQQ3 +ENSG00000114745 GORASP1 testis Leydig cells Medium Enhanced Q9BQQ3 +ENSG00000114757 PEX5L epididymis glandular cells Low Enhanced Q8IYB4 +ENSG00000114757 PEX5L testis cells in seminiferous ducts Low Enhanced Q8IYB4 +ENSG00000114757 PEX5L testis Leydig cells Low Enhanced Q8IYB4 +ENSG00000114779 ABHD14B epididymis glandular cells Medium Supported Q96IU4 +ENSG00000114779 ABHD14B prostate glandular cells Medium Supported Q96IU4 +ENSG00000114779 ABHD14B seminal vesicle glandular cells Medium Supported Q96IU4 +ENSG00000114779 ABHD14B testis cells in seminiferous ducts Medium Supported Q96IU4 +ENSG00000114779 ABHD14B testis Leydig cells Medium Supported Q96IU4 +ENSG00000114861 FOXP1 epididymis glandular cells High Supported Q9H334 +ENSG00000114861 FOXP1 prostate glandular cells Medium Supported Q9H334 +ENSG00000114861 FOXP1 seminal vesicle glandular cells Low Supported Q9H334 +ENSG00000114861 FOXP1 testis cells in seminiferous ducts Medium Supported Q9H334 +ENSG00000114861 FOXP1 testis Leydig cells High Supported Q9H334 +ENSG00000114902 SPCS1 epididymis glandular cells Medium Supported Q9Y6A9 +ENSG00000114902 SPCS1 prostate glandular cells Medium Supported Q9Y6A9 +ENSG00000114902 SPCS1 seminal vesicle glandular cells Medium Supported Q9Y6A9 +ENSG00000114902 SPCS1 testis Leydig cells Low Supported Q9Y6A9 +ENSG00000114942 EEF1B2 epididymis glandular cells Medium Supported NA +ENSG00000114942 EEF1B2 prostate glandular cells Medium Supported NA +ENSG00000114942 EEF1B2 seminal vesicle glandular cells High Supported NA +ENSG00000114942 EEF1B2 testis cells in seminiferous ducts High Supported NA +ENSG00000114942 EEF1B2 testis Leydig cells Medium Supported NA +ENSG00000114978 MOB1A epididymis glandular cells Medium Supported Q9H8S9 +ENSG00000114978 MOB1A prostate glandular cells Medium Supported Q9H8S9 +ENSG00000114978 MOB1A seminal vesicle glandular cells Medium Supported Q9H8S9 +ENSG00000114978 MOB1A testis cells in seminiferous ducts Medium Supported Q9H8S9 +ENSG00000114978 MOB1A testis Leydig cells Medium Supported Q9H8S9 +ENSG00000115042 FAHD2A epididymis glandular cells Medium Enhanced Q96GK7 +ENSG00000115042 FAHD2A prostate glandular cells Low Enhanced Q96GK7 +ENSG00000115042 FAHD2A seminal vesicle glandular cells Medium Enhanced Q96GK7 +ENSG00000115042 FAHD2A testis cells in seminiferous ducts Low Enhanced Q96GK7 +ENSG00000115042 FAHD2A testis Leydig cells High Enhanced Q96GK7 +ENSG00000115053 NCL epididymis glandular cells High Supported P19338 +ENSG00000115053 NCL prostate glandular cells High Supported P19338 +ENSG00000115053 NCL seminal vesicle glandular cells High Supported P19338 +ENSG00000115053 NCL testis cells in seminiferous ducts High Supported P19338 +ENSG00000115053 NCL testis Leydig cells High Supported P19338 +ENSG00000115128 SF3B6 epididymis glandular cells High Enhanced Q9Y3B4 +ENSG00000115128 SF3B6 prostate glandular cells Low Enhanced Q9Y3B4 +ENSG00000115128 SF3B6 seminal vesicle glandular cells Medium Enhanced Q9Y3B4 +ENSG00000115128 SF3B6 testis cells in seminiferous ducts High Enhanced Q9Y3B4 +ENSG00000115128 SF3B6 testis Leydig cells Medium Enhanced Q9Y3B4 +ENSG00000115129 TP53I3 epididymis glandular cells Medium Enhanced Q53FA7 +ENSG00000115129 TP53I3 prostate glandular cells Medium Enhanced Q53FA7 +ENSG00000115129 TP53I3 seminal vesicle glandular cells Medium Enhanced Q53FA7 +ENSG00000115129 TP53I3 testis cells in seminiferous ducts Medium Enhanced Q53FA7 +ENSG00000115129 TP53I3 testis Leydig cells Low Enhanced Q53FA7 +ENSG00000115145 STAM2 epididymis glandular cells Medium Enhanced O75886 +ENSG00000115145 STAM2 prostate glandular cells Medium Enhanced O75886 +ENSG00000115145 STAM2 seminal vesicle glandular cells Medium Enhanced O75886 +ENSG00000115145 STAM2 testis cells in seminiferous ducts High Enhanced O75886 +ENSG00000115145 STAM2 testis Leydig cells Medium Enhanced O75886 +ENSG00000115159 GPD2 epididymis glandular cells Medium Enhanced P43304 +ENSG00000115159 GPD2 prostate glandular cells High Enhanced P43304 +ENSG00000115159 GPD2 seminal vesicle glandular cells Low Enhanced P43304 +ENSG00000115159 GPD2 testis cells in seminiferous ducts Medium Enhanced P43304 +ENSG00000115159 GPD2 testis Leydig cells High Enhanced P43304 +ENSG00000115163 CENPA epididymis glandular cells Low Enhanced P49450 +ENSG00000115163 CENPA testis cells in seminiferous ducts Low Enhanced P49450 +ENSG00000115163 CENPA testis Leydig cells Low Enhanced P49450 +ENSG00000115194 SLC30A3 epididymis glandular cells Medium Enhanced Q99726 +ENSG00000115194 SLC30A3 testis elongated or late spermatids High Enhanced Q99726 +ENSG00000115194 SLC30A3 testis Leydig cells Low Enhanced Q99726 +ENSG00000115194 SLC30A3 testis round or early spermatids High Enhanced Q99726 +ENSG00000115216 NRBP1 epididymis glandular cells Medium Supported Q9UHY1 +ENSG00000115216 NRBP1 prostate glandular cells Medium Supported Q9UHY1 +ENSG00000115216 NRBP1 seminal vesicle glandular cells Medium Supported Q9UHY1 +ENSG00000115216 NRBP1 testis cells in seminiferous ducts Medium Supported Q9UHY1 +ENSG00000115216 NRBP1 testis Leydig cells Medium Supported Q9UHY1 +ENSG00000115234 SNX17 epididymis glandular cells High Supported Q15036 +ENSG00000115234 SNX17 prostate glandular cells Medium Supported Q15036 +ENSG00000115234 SNX17 seminal vesicle glandular cells High Supported Q15036 +ENSG00000115234 SNX17 testis cells in seminiferous ducts Medium Supported Q15036 +ENSG00000115234 SNX17 testis Leydig cells Medium Supported Q15036 +ENSG00000115241 PPM1G epididymis glandular cells Low Enhanced O15355 +ENSG00000115241 PPM1G seminal vesicle glandular cells Medium Enhanced O15355 +ENSG00000115241 PPM1G testis cells in seminiferous ducts High Enhanced O15355 +ENSG00000115241 PPM1G testis Leydig cells High Enhanced O15355 +ENSG00000115255 REEP6 epididymis glandular cells Medium Enhanced Q96HR9 +ENSG00000115255 REEP6 prostate glandular cells Medium Enhanced Q96HR9 +ENSG00000115255 REEP6 seminal vesicle glandular cells Medium Enhanced Q96HR9 +ENSG00000115255 REEP6 testis elongated or late spermatids High Enhanced Q96HR9 +ENSG00000115255 REEP6 testis Leydig cells Medium Enhanced Q96HR9 +ENSG00000115255 REEP6 testis pachytene spermatocytes High Enhanced Q96HR9 +ENSG00000115255 REEP6 testis preleptotene spermatocytes High Enhanced Q96HR9 +ENSG00000115255 REEP6 testis round or early spermatids High Enhanced Q96HR9 +ENSG00000115255 REEP6 testis sertoli cells High Enhanced Q96HR9 +ENSG00000115255 REEP6 testis spermatogonia High Enhanced Q96HR9 +ENSG00000115268 RPS15 epididymis glandular cells Medium Enhanced P62841 +ENSG00000115268 RPS15 prostate glandular cells Medium Enhanced P62841 +ENSG00000115268 RPS15 seminal vesicle glandular cells Medium Enhanced P62841 +ENSG00000115268 RPS15 testis cells in seminiferous ducts Low Enhanced P62841 +ENSG00000115268 RPS15 testis Leydig cells Medium Enhanced P62841 +ENSG00000115289 PCGF1 epididymis glandular cells High Enhanced Q9BSM1 +ENSG00000115289 PCGF1 prostate glandular cells Medium Enhanced Q9BSM1 +ENSG00000115289 PCGF1 seminal vesicle glandular cells High Enhanced Q9BSM1 +ENSG00000115289 PCGF1 testis cells in seminiferous ducts High Enhanced Q9BSM1 +ENSG00000115289 PCGF1 testis Leydig cells High Enhanced Q9BSM1 +ENSG00000115306 SPTBN1 epididymis glandular cells Medium Supported Q01082 +ENSG00000115306 SPTBN1 prostate glandular cells Medium Supported Q01082 +ENSG00000115306 SPTBN1 seminal vesicle glandular cells High Supported Q01082 +ENSG00000115306 SPTBN1 testis cells in seminiferous ducts Medium Supported Q01082 +ENSG00000115306 SPTBN1 testis Leydig cells Medium Supported Q01082 +ENSG00000115310 RTN4 testis cells in seminiferous ducts High Supported Q9NQC3 +ENSG00000115339 GALNT3 epididymis glandular cells High Enhanced Q14435 +ENSG00000115339 GALNT3 prostate glandular cells Medium Enhanced Q14435 +ENSG00000115339 GALNT3 seminal vesicle glandular cells Medium Enhanced Q14435 +ENSG00000115339 GALNT3 testis cells in seminiferous ducts Medium Enhanced Q14435 +ENSG00000115339 GALNT3 testis Leydig cells Medium Enhanced Q14435 +ENSG00000115353 TACR1 prostate glandular cells Medium Enhanced P25103 +ENSG00000115355 CCDC88A testis cells in seminiferous ducts High Enhanced Q3V6T2 +ENSG00000115361 ACADL seminal vesicle glandular cells Low Enhanced P28330 +ENSG00000115361 ACADL testis Leydig cells Low Enhanced P28330 +ENSG00000115392 FANCL epididymis glandular cells Medium Supported Q9NW38 +ENSG00000115392 FANCL prostate glandular cells Medium Supported Q9NW38 +ENSG00000115392 FANCL seminal vesicle glandular cells Medium Supported Q9NW38 +ENSG00000115392 FANCL testis cells in seminiferous ducts Medium Supported Q9NW38 +ENSG00000115392 FANCL testis Leydig cells Medium Supported Q9NW38 +ENSG00000115414 FN1 epididymis glandular cells Low Enhanced P02751 +ENSG00000115414 FN1 seminal vesicle glandular cells Low Enhanced P02751 +ENSG00000115414 FN1 testis cells in seminiferous ducts Low Enhanced P02751 +ENSG00000115414 FN1 testis Leydig cells Medium Enhanced P02751 +ENSG00000115419 GLS epididymis glandular cells Low Enhanced O94925 +ENSG00000115419 GLS prostate glandular cells Low Enhanced O94925 +ENSG00000115419 GLS seminal vesicle glandular cells Medium Enhanced O94925 +ENSG00000115419 GLS testis cells in seminiferous ducts Medium Enhanced O94925 +ENSG00000115419 GLS testis Leydig cells Low Enhanced O94925 +ENSG00000115425 PECR epididymis glandular cells Medium Enhanced Q9BY49 +ENSG00000115425 PECR prostate glandular cells Medium Enhanced Q9BY49 +ENSG00000115425 PECR seminal vesicle glandular cells Medium Enhanced Q9BY49 +ENSG00000115425 PECR testis cells in seminiferous ducts Medium Enhanced Q9BY49 +ENSG00000115425 PECR testis Leydig cells Medium Enhanced Q9BY49 +ENSG00000115468 EFHD1 epididymis glandular cells Low Enhanced Q9BUP0 +ENSG00000115468 EFHD1 prostate glandular cells Medium Enhanced Q9BUP0 +ENSG00000115468 EFHD1 testis cells in seminiferous ducts Low Enhanced Q9BUP0 +ENSG00000115468 EFHD1 testis Leydig cells Medium Enhanced Q9BUP0 +ENSG00000115484 CCT4 seminal vesicle glandular cells Medium Enhanced P50991 +ENSG00000115484 CCT4 testis cells in seminiferous ducts Medium Enhanced P50991 +ENSG00000115504 EHBP1 epididymis glandular cells Medium Enhanced Q8NDI1 +ENSG00000115504 EHBP1 prostate glandular cells Low Enhanced Q8NDI1 +ENSG00000115504 EHBP1 seminal vesicle glandular cells Medium Enhanced Q8NDI1 +ENSG00000115504 EHBP1 testis cells in seminiferous ducts High Enhanced Q8NDI1 +ENSG00000115504 EHBP1 testis Leydig cells Medium Enhanced Q8NDI1 +ENSG00000115541 HSPE1 epididymis glandular cells Medium Supported P61604 +ENSG00000115541 HSPE1 prostate glandular cells High Supported P61604 +ENSG00000115541 HSPE1 seminal vesicle glandular cells High Supported P61604 +ENSG00000115541 HSPE1 testis cells in seminiferous ducts High Supported P61604 +ENSG00000115541 HSPE1 testis Leydig cells High Supported P61604 +ENSG00000115556 PLCD4 testis cells in seminiferous ducts Medium Enhanced Q9BRC7 +ENSG00000115561 CHMP3 epididymis glandular cells High Supported Q9Y3E7 +ENSG00000115561 CHMP3 prostate glandular cells High Supported Q9Y3E7 +ENSG00000115561 CHMP3 seminal vesicle glandular cells High Supported Q9Y3E7 +ENSG00000115561 CHMP3 testis cells in seminiferous ducts High Supported Q9Y3E7 +ENSG00000115561 CHMP3 testis Leydig cells High Supported Q9Y3E7 +ENSG00000115641 FHL2 epididymis glandular cells Low Enhanced Q14192 +ENSG00000115641 FHL2 prostate glandular cells Medium Enhanced Q14192 +ENSG00000115641 FHL2 testis Leydig cells Low Enhanced Q14192 +ENSG00000115677 HDLBP epididymis glandular cells Low Supported Q00341 +ENSG00000115677 HDLBP prostate glandular cells Low Supported Q00341 +ENSG00000115677 HDLBP seminal vesicle glandular cells Medium Supported Q00341 +ENSG00000115677 HDLBP testis cells in seminiferous ducts Low Supported Q00341 +ENSG00000115685 PPP1R7 epididymis glandular cells Medium Supported Q15435 +ENSG00000115685 PPP1R7 prostate glandular cells Medium Supported Q15435 +ENSG00000115685 PPP1R7 seminal vesicle glandular cells Medium Supported Q15435 +ENSG00000115685 PPP1R7 testis cells in seminiferous ducts High Supported Q15435 +ENSG00000115685 PPP1R7 testis Leydig cells Medium Supported Q15435 +ENSG00000115718 PROC testis Leydig cells Low Supported P04070 +ENSG00000115806 GORASP2 epididymis glandular cells High Enhanced Q9H8Y8 +ENSG00000115806 GORASP2 prostate glandular cells High Enhanced Q9H8Y8 +ENSG00000115806 GORASP2 seminal vesicle glandular cells High Enhanced Q9H8Y8 +ENSG00000115806 GORASP2 testis cells in seminiferous ducts Medium Enhanced Q9H8Y8 +ENSG00000115806 GORASP2 testis Leydig cells Medium Enhanced Q9H8Y8 +ENSG00000115828 QPCT epididymis glandular cells Medium Enhanced Q16769 +ENSG00000115828 QPCT seminal vesicle glandular cells Low Enhanced Q16769 +ENSG00000115828 QPCT testis Leydig cells Low Enhanced Q16769 +ENSG00000115840 SLC25A12 epididymis glandular cells High Enhanced O75746 +ENSG00000115840 SLC25A12 prostate glandular cells High Enhanced O75746 +ENSG00000115840 SLC25A12 seminal vesicle glandular cells Medium Enhanced O75746 +ENSG00000115840 SLC25A12 testis cells in seminiferous ducts High Enhanced O75746 +ENSG00000115840 SLC25A12 testis Leydig cells High Enhanced O75746 +ENSG00000115866 DARS epididymis glandular cells Medium Enhanced P14868 +ENSG00000115866 DARS prostate glandular cells Medium Enhanced P14868 +ENSG00000115866 DARS seminal vesicle glandular cells Medium Enhanced P14868 +ENSG00000115866 DARS testis cells in seminiferous ducts Medium Enhanced P14868 +ENSG00000115866 DARS testis Leydig cells Medium Enhanced P14868 +ENSG00000115875 SRSF7 epididymis glandular cells Medium Enhanced Q16629 +ENSG00000115875 SRSF7 prostate glandular cells Low Enhanced Q16629 +ENSG00000115875 SRSF7 seminal vesicle glandular cells Medium Enhanced Q16629 +ENSG00000115875 SRSF7 testis cells in seminiferous ducts Medium Enhanced Q16629 +ENSG00000115875 SRSF7 testis Leydig cells Medium Enhanced Q16629 +ENSG00000115896 PLCL1 epididymis glandular cells Low Enhanced Q15111 +ENSG00000115896 PLCL1 prostate glandular cells Medium Enhanced Q15111 +ENSG00000115896 PLCL1 seminal vesicle glandular cells Medium Enhanced Q15111 +ENSG00000115896 PLCL1 testis cells in seminiferous ducts High Enhanced Q15111 +ENSG00000115896 PLCL1 testis Leydig cells High Enhanced Q15111 +ENSG00000115919 KYNU testis Leydig cells Low Enhanced Q16719 +ENSG00000115935 WIPF1 prostate glandular cells Low Enhanced O43516 +ENSG00000115935 WIPF1 seminal vesicle glandular cells Low Enhanced O43516 +ENSG00000115942 ORC2 testis cells in seminiferous ducts High Enhanced Q13416 +ENSG00000115956 PLEK epididymis glandular cells Low Enhanced P08567 +ENSG00000115966 ATF2 epididymis glandular cells Medium Supported P15336 +ENSG00000115966 ATF2 prostate glandular cells High Supported P15336 +ENSG00000115966 ATF2 seminal vesicle glandular cells Medium Supported P15336 +ENSG00000115966 ATF2 testis cells in seminiferous ducts Medium Supported P15336 +ENSG00000115966 ATF2 testis Leydig cells Medium Supported P15336 +ENSG00000115977 AAK1 epididymis glandular cells Low Enhanced Q2M2I8 +ENSG00000115977 AAK1 seminal vesicle glandular cells Low Enhanced Q2M2I8 +ENSG00000115998 C2orf42 testis Leydig cells Low Enhanced Q9NWW7 +ENSG00000115998 C2orf42 testis pachytene spermatocytes Low Enhanced Q9NWW7 +ENSG00000115998 C2orf42 testis preleptotene spermatocytes Low Enhanced Q9NWW7 +ENSG00000115998 C2orf42 testis round or early spermatids High Enhanced Q9NWW7 +ENSG00000115998 C2orf42 testis spermatogonia Low Enhanced Q9NWW7 +ENSG00000116017 ARID3A testis cells in seminiferous ducts High Enhanced Q99856 +ENSG00000116030 SUMO1 epididymis glandular cells High Supported P63165 +ENSG00000116030 SUMO1 prostate glandular cells Medium Supported P63165 +ENSG00000116030 SUMO1 seminal vesicle glandular cells Medium Supported P63165 +ENSG00000116030 SUMO1 testis cells in seminiferous ducts High Supported P63165 +ENSG00000116030 SUMO1 testis Leydig cells Low Supported P63165 +ENSG00000116039 ATP6V1B1 epididymis glandular cells Medium Enhanced P15313 +ENSG00000116039 ATP6V1B1 prostate glandular cells Low Enhanced P15313 +ENSG00000116039 ATP6V1B1 seminal vesicle glandular cells Medium Enhanced P15313 +ENSG00000116039 ATP6V1B1 testis Leydig cells Low Enhanced P15313 +ENSG00000116044 NFE2L2 epididymis glandular cells Medium Enhanced Q16236 +ENSG00000116044 NFE2L2 prostate glandular cells Medium Enhanced Q16236 +ENSG00000116044 NFE2L2 seminal vesicle glandular cells Medium Enhanced Q16236 +ENSG00000116044 NFE2L2 testis cells in seminiferous ducts Medium Enhanced Q16236 +ENSG00000116044 NFE2L2 testis Leydig cells Medium Enhanced Q16236 +ENSG00000116062 MSH6 epididymis glandular cells High Enhanced P52701 +ENSG00000116062 MSH6 prostate glandular cells High Enhanced P52701 +ENSG00000116062 MSH6 seminal vesicle glandular cells High Enhanced P52701 +ENSG00000116062 MSH6 testis cells in seminiferous ducts High Enhanced P52701 +ENSG00000116062 MSH6 testis Leydig cells High Enhanced P52701 +ENSG00000116106 EPHA4 prostate glandular cells Low Enhanced P54764 +ENSG00000116106 EPHA4 testis cells in seminiferous ducts Medium Enhanced P54764 +ENSG00000116120 FARSB epididymis glandular cells Low Enhanced Q9NSD9 +ENSG00000116120 FARSB testis cells in seminiferous ducts Medium Enhanced Q9NSD9 +ENSG00000116127 ALMS1 epididymis glandular cells Low Enhanced Q8TCU4 +ENSG00000116127 ALMS1 prostate glandular cells Low Enhanced Q8TCU4 +ENSG00000116127 ALMS1 seminal vesicle glandular cells Low Enhanced Q8TCU4 +ENSG00000116127 ALMS1 testis elongated or late spermatids High Enhanced Q8TCU4 +ENSG00000116127 ALMS1 testis pachytene spermatocytes High Enhanced Q8TCU4 +ENSG00000116127 ALMS1 testis round or early spermatids High Enhanced Q8TCU4 +ENSG00000116128 BCL9 epididymis glandular cells Medium Enhanced O00512 +ENSG00000116128 BCL9 prostate glandular cells Medium Enhanced O00512 +ENSG00000116128 BCL9 seminal vesicle glandular cells Medium Enhanced O00512 +ENSG00000116128 BCL9 testis cells in seminiferous ducts Medium Enhanced O00512 +ENSG00000116128 BCL9 testis Leydig cells Low Enhanced O00512 +ENSG00000116171 SCP2 epididymis glandular cells Medium Supported P22307 +ENSG00000116171 SCP2 prostate glandular cells Medium Supported P22307 +ENSG00000116171 SCP2 seminal vesicle glandular cells Low Supported P22307 +ENSG00000116171 SCP2 testis cells in seminiferous ducts Medium Supported P22307 +ENSG00000116171 SCP2 testis Leydig cells Medium Supported P22307 +ENSG00000116191 RALGPS2 epididymis glandular cells Low Enhanced Q86X27 +ENSG00000116191 RALGPS2 testis cells in seminiferous ducts High Enhanced Q86X27 +ENSG00000116191 RALGPS2 testis elongated or late spermatids High Enhanced Q86X27 +ENSG00000116191 RALGPS2 testis pachytene spermatocytes High Enhanced Q86X27 +ENSG00000116191 RALGPS2 testis peritubular cells Low Enhanced Q86X27 +ENSG00000116191 RALGPS2 testis preleptotene spermatocytes Low Enhanced Q86X27 +ENSG00000116191 RALGPS2 testis round or early spermatids High Enhanced Q86X27 +ENSG00000116191 RALGPS2 testis spermatogonia Low Enhanced Q86X27 +ENSG00000116221 MRPL37 epididymis glandular cells Low Enhanced Q9BZE1 +ENSG00000116221 MRPL37 prostate glandular cells Low Enhanced Q9BZE1 +ENSG00000116221 MRPL37 seminal vesicle glandular cells Medium Enhanced Q9BZE1 +ENSG00000116221 MRPL37 testis cells in seminiferous ducts Low Enhanced Q9BZE1 +ENSG00000116221 MRPL37 testis Leydig cells Medium Enhanced Q9BZE1 +ENSG00000116288 PARK7 epididymis glandular cells High Enhanced Q99497 +ENSG00000116288 PARK7 prostate glandular cells High Enhanced Q99497 +ENSG00000116288 PARK7 seminal vesicle glandular cells High Enhanced Q99497 +ENSG00000116288 PARK7 testis cells in seminiferous ducts High Enhanced Q99497 +ENSG00000116288 PARK7 testis Leydig cells High Enhanced Q99497 +ENSG00000116299 KIAA1324 prostate glandular cells High Enhanced Q6UXG2 +ENSG00000116299 KIAA1324 seminal vesicle glandular cells Low Enhanced Q6UXG2 +ENSG00000116299 KIAA1324 testis cells in seminiferous ducts High Enhanced Q6UXG2 +ENSG00000116350 SRSF4 epididymis glandular cells Medium Supported Q08170 +ENSG00000116350 SRSF4 prostate glandular cells Medium Supported Q08170 +ENSG00000116350 SRSF4 seminal vesicle glandular cells Medium Supported Q08170 +ENSG00000116350 SRSF4 testis cells in seminiferous ducts Low Supported Q08170 +ENSG00000116350 SRSF4 testis Leydig cells High Supported Q08170 +ENSG00000116353 MECR epididymis glandular cells Medium Enhanced Q9BV79 +ENSG00000116353 MECR prostate glandular cells Medium Enhanced Q9BV79 +ENSG00000116353 MECR seminal vesicle glandular cells Medium Enhanced Q9BV79 +ENSG00000116353 MECR testis cells in seminiferous ducts Medium Enhanced Q9BV79 +ENSG00000116353 MECR testis Leydig cells Medium Enhanced Q9BV79 +ENSG00000116459 ATP5F1 epididymis glandular cells Medium Enhanced P24539 +ENSG00000116459 ATP5F1 prostate glandular cells Medium Enhanced P24539 +ENSG00000116459 ATP5F1 seminal vesicle glandular cells Medium Enhanced P24539 +ENSG00000116459 ATP5F1 testis cells in seminiferous ducts Medium Enhanced P24539 +ENSG00000116459 ATP5F1 testis Leydig cells Medium Enhanced P24539 +ENSG00000116478 HDAC1 epididymis glandular cells High Enhanced Q13547 +ENSG00000116478 HDAC1 prostate glandular cells Medium Enhanced Q13547 +ENSG00000116478 HDAC1 seminal vesicle glandular cells Medium Enhanced Q13547 +ENSG00000116478 HDAC1 testis cells in seminiferous ducts Medium Enhanced Q13547 +ENSG00000116478 HDAC1 testis Leydig cells Medium Enhanced Q13547 +ENSG00000116560 SFPQ epididymis glandular cells High Enhanced P23246 +ENSG00000116560 SFPQ prostate glandular cells High Enhanced P23246 +ENSG00000116560 SFPQ seminal vesicle glandular cells High Enhanced P23246 +ENSG00000116560 SFPQ testis cells in seminiferous ducts High Enhanced P23246 +ENSG00000116560 SFPQ testis Leydig cells High Enhanced P23246 +ENSG00000116604 MEF2D epididymis glandular cells High Enhanced Q14814 +ENSG00000116604 MEF2D prostate glandular cells Medium Enhanced Q14814 +ENSG00000116604 MEF2D seminal vesicle glandular cells Medium Enhanced Q14814 +ENSG00000116604 MEF2D testis cells in seminiferous ducts High Enhanced Q14814 +ENSG00000116604 MEF2D testis Leydig cells High Enhanced Q14814 +ENSG00000116668 SWT1 epididymis glandular cells Medium Enhanced Q5T5J6 +ENSG00000116668 SWT1 prostate glandular cells Medium Enhanced Q5T5J6 +ENSG00000116668 SWT1 seminal vesicle glandular cells Medium Enhanced Q5T5J6 +ENSG00000116668 SWT1 testis cells in seminiferous ducts Medium Enhanced Q5T5J6 +ENSG00000116668 SWT1 testis Leydig cells Medium Enhanced Q5T5J6 +ENSG00000116698 SMG7 prostate glandular cells Medium Supported Q92540 +ENSG00000116698 SMG7 seminal vesicle glandular cells Medium Supported Q92540 +ENSG00000116752 BCAS2 epididymis glandular cells Medium Enhanced O75934 +ENSG00000116752 BCAS2 prostate glandular cells Low Enhanced O75934 +ENSG00000116752 BCAS2 seminal vesicle glandular cells Low Enhanced O75934 +ENSG00000116752 BCAS2 testis cells in seminiferous ducts Medium Enhanced O75934 +ENSG00000116752 BCAS2 testis Leydig cells Medium Enhanced O75934 +ENSG00000116754 SRSF11 epididymis glandular cells High Supported Q05519 +ENSG00000116754 SRSF11 prostate glandular cells High Supported Q05519 +ENSG00000116754 SRSF11 seminal vesicle glandular cells High Supported Q05519 +ENSG00000116754 SRSF11 testis cells in seminiferous ducts High Supported Q05519 +ENSG00000116754 SRSF11 testis Leydig cells High Supported Q05519 +ENSG00000116761 CTH testis Leydig cells Low Enhanced P32929 +ENSG00000116771 AGMAT epididymis glandular cells Low Enhanced Q9BSE5 +ENSG00000116771 AGMAT testis Leydig cells Low Enhanced Q9BSE5 +ENSG00000116833 NR5A2 epididymis glandular cells High Supported O00482 +ENSG00000116833 NR5A2 prostate glandular cells High Supported O00482 +ENSG00000116833 NR5A2 seminal vesicle glandular cells High Supported O00482 +ENSG00000116833 NR5A2 testis cells in seminiferous ducts High Supported O00482 +ENSG00000116833 NR5A2 testis Leydig cells High Supported O00482 +ENSG00000116874 WARS2 epididymis glandular cells Low Enhanced Q9UGM6 +ENSG00000116874 WARS2 prostate glandular cells Medium Enhanced Q9UGM6 +ENSG00000116874 WARS2 seminal vesicle glandular cells Medium Enhanced Q9UGM6 +ENSG00000116874 WARS2 testis cells in seminiferous ducts Medium Enhanced Q9UGM6 +ENSG00000116874 WARS2 testis Leydig cells Medium Enhanced Q9UGM6 +ENSG00000116898 MRPS15 epididymis glandular cells High Enhanced P82914 +ENSG00000116898 MRPS15 prostate glandular cells High Enhanced P82914 +ENSG00000116898 MRPS15 seminal vesicle glandular cells Medium Enhanced P82914 +ENSG00000116898 MRPS15 testis cells in seminiferous ducts Low Enhanced P82914 +ENSG00000116898 MRPS15 testis Leydig cells Medium Enhanced P82914 +ENSG00000116922 C1orf109 epididymis glandular cells Low Supported Q9NX04 +ENSG00000116922 C1orf109 prostate glandular cells Low Supported Q9NX04 +ENSG00000116922 C1orf109 seminal vesicle glandular cells Medium Supported Q9NX04 +ENSG00000116922 C1orf109 testis cells in seminiferous ducts Medium Supported Q9NX04 +ENSG00000116922 C1orf109 testis Leydig cells Medium Supported Q9NX04 +ENSG00000116954 RRAGC epididymis glandular cells Medium Enhanced Q9HB90 +ENSG00000116954 RRAGC prostate glandular cells Medium Enhanced Q9HB90 +ENSG00000116954 RRAGC seminal vesicle glandular cells Medium Enhanced Q9HB90 +ENSG00000116954 RRAGC testis cells in seminiferous ducts High Enhanced Q9HB90 +ENSG00000116954 RRAGC testis Leydig cells Medium Enhanced Q9HB90 +ENSG00000116981 NT5C1A epididymis glandular cells Medium Supported Q9BXI3 +ENSG00000116981 NT5C1A prostate glandular cells Medium Supported Q9BXI3 +ENSG00000116981 NT5C1A seminal vesicle glandular cells Low Supported Q9BXI3 +ENSG00000116981 NT5C1A testis cells in seminiferous ducts Medium Supported Q9BXI3 +ENSG00000116981 NT5C1A testis Leydig cells Medium Supported Q9BXI3 +ENSG00000117036 ETV3 epididymis glandular cells High Supported P41162 +ENSG00000117036 ETV3 prostate glandular cells Medium Supported P41162 +ENSG00000117036 ETV3 testis cells in seminiferous ducts Medium Supported P41162 +ENSG00000117036 ETV3 testis Leydig cells Medium Supported P41162 +ENSG00000117054 ACADM epididymis glandular cells High Enhanced P11310 +ENSG00000117054 ACADM prostate glandular cells Low Enhanced P11310 +ENSG00000117054 ACADM seminal vesicle glandular cells High Enhanced P11310 +ENSG00000117054 ACADM testis cells in seminiferous ducts High Enhanced P11310 +ENSG00000117054 ACADM testis Leydig cells Medium Enhanced P11310 +ENSG00000117118 SDHB epididymis glandular cells Medium Enhanced P21912 +ENSG00000117118 SDHB prostate glandular cells Medium Enhanced P21912 +ENSG00000117118 SDHB seminal vesicle glandular cells Medium Enhanced P21912 +ENSG00000117118 SDHB testis cells in seminiferous ducts High Enhanced P21912 +ENSG00000117118 SDHB testis Leydig cells High Enhanced P21912 +ENSG00000117133 RPF1 epididymis glandular cells Low Supported Q9H9Y2 +ENSG00000117133 RPF1 seminal vesicle glandular cells Low Supported Q9H9Y2 +ENSG00000117133 RPF1 testis cells in seminiferous ducts Low Supported Q9H9Y2 +ENSG00000117133 RPF1 testis Leydig cells Medium Supported Q9H9Y2 +ENSG00000117139 KDM5B epididymis glandular cells Medium Enhanced Q9UGL1 +ENSG00000117139 KDM5B seminal vesicle glandular cells Low Enhanced Q9UGL1 +ENSG00000117139 KDM5B testis Leydig cells Medium Enhanced Q9UGL1 +ENSG00000117139 KDM5B testis pachytene spermatocytes High Enhanced Q9UGL1 +ENSG00000117139 KDM5B testis peritubular cells Medium Enhanced Q9UGL1 +ENSG00000117139 KDM5B testis preleptotene spermatocytes Medium Enhanced Q9UGL1 +ENSG00000117139 KDM5B testis round or early spermatids Medium Enhanced Q9UGL1 +ENSG00000117139 KDM5B testis spermatogonia Medium Enhanced Q9UGL1 +ENSG00000117245 KIF17 testis cells in seminiferous ducts Medium Enhanced Q9P2E2 +ENSG00000117305 HMGCL epididymis glandular cells High Enhanced P35914 +ENSG00000117305 HMGCL prostate glandular cells Medium Enhanced P35914 +ENSG00000117305 HMGCL seminal vesicle glandular cells High Enhanced P35914 +ENSG00000117305 HMGCL testis cells in seminiferous ducts Medium Enhanced P35914 +ENSG00000117305 HMGCL testis Leydig cells Medium Enhanced P35914 +ENSG00000117335 CD46 epididymis glandular cells Medium Enhanced P15529 +ENSG00000117335 CD46 prostate glandular cells Medium Enhanced P15529 +ENSG00000117335 CD46 seminal vesicle glandular cells Medium Enhanced P15529 +ENSG00000117335 CD46 testis cells in seminiferous ducts Medium Enhanced P15529 +ENSG00000117335 CD46 testis Leydig cells Medium Enhanced P15529 +ENSG00000117399 CDC20 testis pachytene spermatocytes High Enhanced Q12834 +ENSG00000117399 CDC20 testis spermatogonia High Enhanced Q12834 +ENSG00000117411 B4GALT2 epididymis glandular cells High Enhanced O60909 +ENSG00000117411 B4GALT2 prostate glandular cells High Enhanced O60909 +ENSG00000117411 B4GALT2 seminal vesicle glandular cells High Enhanced O60909 +ENSG00000117411 B4GALT2 testis cells in seminiferous ducts Low Enhanced O60909 +ENSG00000117411 B4GALT2 testis Leydig cells Medium Enhanced O60909 +ENSG00000117475 BLZF1 epididymis glandular cells Medium Supported Q9H2G9 +ENSG00000117475 BLZF1 prostate glandular cells Medium Supported Q9H2G9 +ENSG00000117475 BLZF1 seminal vesicle glandular cells Medium Supported Q9H2G9 +ENSG00000117475 BLZF1 testis cells in seminiferous ducts Medium Supported Q9H2G9 +ENSG00000117475 BLZF1 testis Leydig cells High Supported Q9H2G9 +ENSG00000117477 CCDC181 epididymis glandular cells Medium Enhanced Q5TID7 +ENSG00000117505 DR1 epididymis glandular cells Medium Enhanced Q01658 +ENSG00000117505 DR1 prostate glandular cells Medium Enhanced Q01658 +ENSG00000117505 DR1 seminal vesicle glandular cells Medium Enhanced Q01658 +ENSG00000117505 DR1 testis cells in seminiferous ducts High Enhanced Q01658 +ENSG00000117505 DR1 testis Leydig cells Medium Enhanced Q01658 +ENSG00000117519 CNN3 epididymis glandular cells Medium Enhanced Q15417 +ENSG00000117519 CNN3 prostate glandular cells Medium Enhanced Q15417 +ENSG00000117519 CNN3 seminal vesicle glandular cells Medium Enhanced Q15417 +ENSG00000117519 CNN3 testis cells in seminiferous ducts Low Enhanced Q15417 +ENSG00000117519 CNN3 testis Leydig cells Medium Enhanced Q15417 +ENSG00000117528 ABCD3 epididymis glandular cells High Enhanced P28288 +ENSG00000117528 ABCD3 prostate glandular cells High Enhanced P28288 +ENSG00000117528 ABCD3 seminal vesicle glandular cells High Enhanced P28288 +ENSG00000117528 ABCD3 testis cells in seminiferous ducts High Enhanced P28288 +ENSG00000117528 ABCD3 testis Leydig cells Medium Enhanced P28288 +ENSG00000117533 VAMP4 epididymis glandular cells Medium Enhanced O75379 +ENSG00000117533 VAMP4 prostate glandular cells Medium Enhanced O75379 +ENSG00000117533 VAMP4 seminal vesicle glandular cells High Enhanced O75379 +ENSG00000117533 VAMP4 testis cells in seminiferous ducts Medium Enhanced O75379 +ENSG00000117533 VAMP4 testis Leydig cells Medium Enhanced O75379 +ENSG00000117592 PRDX6 epididymis glandular cells High Supported P30041 +ENSG00000117592 PRDX6 prostate glandular cells High Supported P30041 +ENSG00000117592 PRDX6 seminal vesicle glandular cells Medium Supported P30041 +ENSG00000117592 PRDX6 testis cells in seminiferous ducts High Supported P30041 +ENSG00000117592 PRDX6 testis Leydig cells High Supported P30041 +ENSG00000117593 DARS2 epididymis glandular cells High Enhanced Q6PI48 +ENSG00000117593 DARS2 prostate glandular cells Medium Enhanced Q6PI48 +ENSG00000117593 DARS2 seminal vesicle glandular cells Medium Enhanced Q6PI48 +ENSG00000117593 DARS2 testis cells in seminiferous ducts Medium Enhanced Q6PI48 +ENSG00000117593 DARS2 testis Leydig cells Medium Enhanced Q6PI48 +ENSG00000117595 IRF6 epididymis glandular cells Medium Enhanced O14896 +ENSG00000117595 IRF6 prostate glandular cells Medium Enhanced O14896 +ENSG00000117595 IRF6 seminal vesicle glandular cells Medium Enhanced O14896 +ENSG00000117595 IRF6 testis cells in seminiferous ducts Medium Enhanced O14896 +ENSG00000117595 IRF6 testis Leydig cells Low Enhanced O14896 +ENSG00000117601 SERPINC1 epididymis glandular cells Medium Supported P01008 +ENSG00000117601 SERPINC1 prostate glandular cells Medium Supported P01008 +ENSG00000117601 SERPINC1 seminal vesicle glandular cells Medium Supported P01008 +ENSG00000117601 SERPINC1 testis cells in seminiferous ducts Medium Supported P01008 +ENSG00000117601 SERPINC1 testis Leydig cells Medium Supported P01008 +ENSG00000117602 RCAN3 prostate glandular cells Medium Enhanced Q9UKA8 +ENSG00000117602 RCAN3 testis Leydig cells Medium Enhanced Q9UKA8 +ENSG00000117625 RCOR3 epididymis glandular cells Medium Enhanced Q9P2K3 +ENSG00000117625 RCOR3 prostate glandular cells Low Enhanced Q9P2K3 +ENSG00000117625 RCOR3 seminal vesicle glandular cells Medium Enhanced Q9P2K3 +ENSG00000117625 RCOR3 testis cells in seminiferous ducts High Enhanced Q9P2K3 +ENSG00000117625 RCOR3 testis Leydig cells Low Enhanced Q9P2K3 +ENSG00000117650 NEK2 testis cells in seminiferous ducts Low Enhanced P51955 +ENSG00000117676 RPS6KA1 epididymis glandular cells Medium Enhanced NA +ENSG00000117676 RPS6KA1 prostate glandular cells Medium Enhanced NA +ENSG00000117676 RPS6KA1 seminal vesicle glandular cells Medium Enhanced NA +ENSG00000117676 RPS6KA1 testis cells in seminiferous ducts Medium Enhanced NA +ENSG00000117676 RPS6KA1 testis Leydig cells Medium Enhanced NA +ENSG00000117697 NSL1 epididymis glandular cells High Enhanced Q96IY1 +ENSG00000117697 NSL1 prostate glandular cells Medium Enhanced Q96IY1 +ENSG00000117697 NSL1 seminal vesicle glandular cells Medium Enhanced Q96IY1 +ENSG00000117697 NSL1 testis cells in seminiferous ducts Medium Enhanced Q96IY1 +ENSG00000117697 NSL1 testis Leydig cells Medium Enhanced Q96IY1 +ENSG00000117713 ARID1A epididymis glandular cells Medium Supported O14497 +ENSG00000117713 ARID1A prostate glandular cells Medium Supported O14497 +ENSG00000117713 ARID1A seminal vesicle glandular cells Medium Supported O14497 +ENSG00000117713 ARID1A testis cells in seminiferous ducts Medium Supported O14497 +ENSG00000117724 CENPF epididymis glandular cells Medium Enhanced P49454 +ENSG00000117724 CENPF testis cells in seminiferous ducts Medium Enhanced P49454 +ENSG00000117724 CENPF testis Leydig cells Medium Enhanced P49454 +ENSG00000117748 RPA2 epididymis glandular cells High Supported P15927 +ENSG00000117748 RPA2 prostate glandular cells High Supported P15927 +ENSG00000117748 RPA2 seminal vesicle glandular cells High Supported P15927 +ENSG00000117748 RPA2 testis cells in seminiferous ducts High Supported P15927 +ENSG00000117748 RPA2 testis Leydig cells High Supported P15927 +ENSG00000117751 PPP1R8 epididymis glandular cells High Enhanced Q12972 +ENSG00000117751 PPP1R8 prostate glandular cells High Enhanced Q12972 +ENSG00000117751 PPP1R8 seminal vesicle glandular cells High Enhanced Q12972 +ENSG00000117751 PPP1R8 testis cells in seminiferous ducts High Enhanced Q12972 +ENSG00000117751 PPP1R8 testis Leydig cells High Enhanced Q12972 +ENSG00000117791 MARC2 epididymis glandular cells Medium Enhanced Q969Z3 +ENSG00000117791 MARC2 prostate glandular cells Low Enhanced Q969Z3 +ENSG00000117791 MARC2 seminal vesicle glandular cells Medium Enhanced Q969Z3 +ENSG00000117791 MARC2 testis cells in seminiferous ducts Medium Enhanced Q969Z3 +ENSG00000117791 MARC2 testis Leydig cells Low Enhanced Q969Z3 +ENSG00000117859 OSBPL9 epididymis glandular cells Medium Supported Q96SU4 +ENSG00000117859 OSBPL9 prostate glandular cells Low Supported Q96SU4 +ENSG00000117859 OSBPL9 seminal vesicle glandular cells Medium Supported Q96SU4 +ENSG00000117859 OSBPL9 testis cells in seminiferous ducts Medium Supported Q96SU4 +ENSG00000117859 OSBPL9 testis Leydig cells Medium Supported Q96SU4 +ENSG00000117877 CD3EAP epididymis glandular cells Medium Supported O15446 +ENSG00000117877 CD3EAP prostate glandular cells Low Supported O15446 +ENSG00000117877 CD3EAP seminal vesicle glandular cells Low Supported O15446 +ENSG00000117877 CD3EAP testis cells in seminiferous ducts Medium Supported O15446 +ENSG00000117877 CD3EAP testis Leydig cells Low Supported O15446 +ENSG00000117906 RCN2 epididymis glandular cells High Enhanced Q14257 +ENSG00000117906 RCN2 testis cells in seminiferous ducts High Enhanced Q14257 +ENSG00000117984 CTSD epididymis glandular cells Medium Enhanced P07339 +ENSG00000117984 CTSD prostate glandular cells Medium Enhanced P07339 +ENSG00000117984 CTSD seminal vesicle glandular cells Medium Enhanced P07339 +ENSG00000117984 CTSD testis cells in seminiferous ducts Medium Enhanced P07339 +ENSG00000117984 CTSD testis Leydig cells Medium Enhanced P07339 +ENSG00000118007 STAG1 epididymis glandular cells High Supported Q8WVM7 +ENSG00000118007 STAG1 prostate glandular cells High Supported Q8WVM7 +ENSG00000118007 STAG1 seminal vesicle glandular cells Medium Supported Q8WVM7 +ENSG00000118007 STAG1 testis cells in seminiferous ducts High Supported Q8WVM7 +ENSG00000118007 STAG1 testis Leydig cells High Supported Q8WVM7 +ENSG00000118058 KMT2A epididymis glandular cells Medium Enhanced Q03164 +ENSG00000118058 KMT2A prostate glandular cells Medium Enhanced Q03164 +ENSG00000118058 KMT2A seminal vesicle glandular cells Medium Enhanced Q03164 +ENSG00000118058 KMT2A testis cells in seminiferous ducts Low Enhanced Q03164 +ENSG00000118058 KMT2A testis Leydig cells Low Enhanced Q03164 +ENSG00000118156 ZNF541 testis cells in seminiferous ducts Medium Enhanced Q9H0D2 +ENSG00000118200 CAMSAP2 epididymis glandular cells Medium Enhanced Q08AD1 +ENSG00000118200 CAMSAP2 prostate glandular cells Medium Enhanced Q08AD1 +ENSG00000118200 CAMSAP2 seminal vesicle glandular cells Medium Enhanced Q08AD1 +ENSG00000118200 CAMSAP2 testis cells in seminiferous ducts Medium Enhanced Q08AD1 +ENSG00000118200 CAMSAP2 testis Leydig cells High Enhanced Q08AD1 +ENSG00000118245 TNP1 testis elongated or late spermatids High Enhanced P09430 +ENSG00000118245 TNP1 testis round or early spermatids High Enhanced P09430 +ENSG00000118257 NRP2 epididymis glandular cells Medium Enhanced O60462 +ENSG00000118257 NRP2 prostate glandular cells Low Enhanced O60462 +ENSG00000118257 NRP2 seminal vesicle glandular cells Low Enhanced O60462 +ENSG00000118257 NRP2 testis Leydig cells Medium Enhanced O60462 +ENSG00000118260 CREB1 epididymis glandular cells High Supported P16220 +ENSG00000118260 CREB1 prostate glandular cells High Supported P16220 +ENSG00000118260 CREB1 seminal vesicle glandular cells High Supported P16220 +ENSG00000118260 CREB1 testis cells in seminiferous ducts High Supported P16220 +ENSG00000118260 CREB1 testis Leydig cells High Supported P16220 +ENSG00000118307 CASC1 testis elongated or late spermatids High Enhanced Q6TDU7 +ENSG00000118307 CASC1 testis Leydig cells Low Enhanced Q6TDU7 +ENSG00000118307 CASC1 testis round or early spermatids High Enhanced Q6TDU7 +ENSG00000118307 CASC1 testis spermatogonia Low Enhanced Q6TDU7 +ENSG00000118407 FILIP1 testis cells in seminiferous ducts Low Enhanced Q7Z7B0 +ENSG00000118407 FILIP1 testis Leydig cells Low Enhanced Q7Z7B0 +ENSG00000118418 HMGN3 epididymis glandular cells Medium Enhanced Q15651 +ENSG00000118418 HMGN3 testis Leydig cells High Enhanced Q15651 +ENSG00000118434 SPACA1 testis elongated or late spermatids High Enhanced Q9HBV2 +ENSG00000118434 SPACA1 testis Leydig cells Low Enhanced Q9HBV2 +ENSG00000118434 SPACA1 testis round or early spermatids High Enhanced Q9HBV2 +ENSG00000118492 ADGB testis elongated or late spermatids Medium Enhanced Q8N7X0 +ENSG00000118492 ADGB testis pachytene spermatocytes Medium Enhanced Q8N7X0 +ENSG00000118492 ADGB testis preleptotene spermatocytes Low Enhanced Q8N7X0 +ENSG00000118492 ADGB testis round or early spermatids Medium Enhanced Q8N7X0 +ENSG00000118492 ADGB testis spermatogonia Low Enhanced Q8N7X0 +ENSG00000118640 VAMP8 epididymis glandular cells High Enhanced Q9BV40 +ENSG00000118640 VAMP8 prostate glandular cells High Enhanced Q9BV40 +ENSG00000118640 VAMP8 seminal vesicle glandular cells High Enhanced Q9BV40 +ENSG00000118640 VAMP8 testis cells in seminiferous ducts Medium Enhanced Q9BV40 +ENSG00000118640 VAMP8 testis Leydig cells Medium Enhanced Q9BV40 +ENSG00000118689 FOXO3 epididymis glandular cells Medium Supported O43524 +ENSG00000118689 FOXO3 prostate glandular cells Medium Supported O43524 +ENSG00000118689 FOXO3 seminal vesicle glandular cells Medium Supported O43524 +ENSG00000118689 FOXO3 testis cells in seminiferous ducts High Supported O43524 +ENSG00000118689 FOXO3 testis Leydig cells Medium Supported O43524 +ENSG00000118690 ARMC2 testis cells in seminiferous ducts Medium Enhanced Q8NEN0 +ENSG00000118705 RPN2 epididymis glandular cells High Enhanced P04844 +ENSG00000118705 RPN2 prostate glandular cells Medium Enhanced P04844 +ENSG00000118705 RPN2 seminal vesicle glandular cells High Enhanced P04844 +ENSG00000118705 RPN2 testis cells in seminiferous ducts Medium Enhanced P04844 +ENSG00000118705 RPN2 testis Leydig cells Medium Enhanced P04844 +ENSG00000118777 ABCG2 seminal vesicle glandular cells High Enhanced Q9UNQ0 +ENSG00000118777 ABCG2 testis cells in seminiferous ducts Low Enhanced Q9UNQ0 +ENSG00000118785 SPP1 epididymis glandular cells Low Enhanced P10451 +ENSG00000118804 STBD1 epididymis glandular cells Low Enhanced O95210 +ENSG00000118804 STBD1 prostate glandular cells Low Enhanced O95210 +ENSG00000118804 STBD1 seminal vesicle glandular cells Low Enhanced O95210 +ENSG00000118804 STBD1 testis cells in seminiferous ducts Medium Enhanced O95210 +ENSG00000118804 STBD1 testis Leydig cells Medium Enhanced O95210 +ENSG00000118898 PPL epididymis glandular cells Low Enhanced O60437 +ENSG00000118898 PPL prostate glandular cells Medium Enhanced O60437 +ENSG00000118898 PPL seminal vesicle glandular cells Medium Enhanced O60437 +ENSG00000118900 UBN1 epididymis glandular cells Medium Enhanced Q9NPG3 +ENSG00000118900 UBN1 prostate glandular cells Medium Enhanced Q9NPG3 +ENSG00000118900 UBN1 seminal vesicle glandular cells Medium Enhanced Q9NPG3 +ENSG00000118900 UBN1 testis cells in seminiferous ducts Medium Enhanced Q9NPG3 +ENSG00000118900 UBN1 testis Leydig cells Medium Enhanced Q9NPG3 +ENSG00000119139 TJP2 epididymis glandular cells Medium Supported Q9UDY2 +ENSG00000119139 TJP2 prostate glandular cells Medium Supported Q9UDY2 +ENSG00000119139 TJP2 seminal vesicle glandular cells Medium Supported Q9UDY2 +ENSG00000119139 TJP2 testis cells in seminiferous ducts Medium Supported Q9UDY2 +ENSG00000119139 TJP2 testis Leydig cells Low Supported Q9UDY2 +ENSG00000119318 RAD23B epididymis glandular cells High Enhanced P54727 +ENSG00000119318 RAD23B prostate glandular cells High Enhanced P54727 +ENSG00000119318 RAD23B seminal vesicle glandular cells High Enhanced P54727 +ENSG00000119318 RAD23B testis cells in seminiferous ducts High Enhanced P54727 +ENSG00000119318 RAD23B testis Leydig cells High Enhanced P54727 +ENSG00000119335 SET epididymis glandular cells High Supported Q01105 +ENSG00000119335 SET prostate glandular cells Medium Supported Q01105 +ENSG00000119335 SET seminal vesicle glandular cells High Supported Q01105 +ENSG00000119335 SET testis cells in seminiferous ducts Medium Supported Q01105 +ENSG00000119335 SET testis Leydig cells High Supported Q01105 +ENSG00000119392 GLE1 epididymis glandular cells Medium Supported Q53GS7 +ENSG00000119392 GLE1 prostate glandular cells Medium Supported Q53GS7 +ENSG00000119392 GLE1 seminal vesicle glandular cells Medium Supported Q53GS7 +ENSG00000119392 GLE1 testis cells in seminiferous ducts Medium Supported Q53GS7 +ENSG00000119392 GLE1 testis Leydig cells Medium Supported Q53GS7 +ENSG00000119421 NDUFA8 epididymis glandular cells Medium Enhanced P51970 +ENSG00000119421 NDUFA8 prostate glandular cells Medium Enhanced P51970 +ENSG00000119421 NDUFA8 seminal vesicle glandular cells High Enhanced P51970 +ENSG00000119421 NDUFA8 testis cells in seminiferous ducts High Enhanced P51970 +ENSG00000119421 NDUFA8 testis Leydig cells Medium Enhanced P51970 +ENSG00000119431 HDHD3 epididymis glandular cells Medium Enhanced Q9BSH5 +ENSG00000119431 HDHD3 prostate glandular cells Medium Enhanced Q9BSH5 +ENSG00000119431 HDHD3 seminal vesicle glandular cells Medium Enhanced Q9BSH5 +ENSG00000119431 HDHD3 testis cells in seminiferous ducts Medium Enhanced Q9BSH5 +ENSG00000119431 HDHD3 testis Leydig cells High Enhanced Q9BSH5 +ENSG00000119471 HSDL2 epididymis glandular cells Medium Enhanced Q6YN16 +ENSG00000119471 HSDL2 prostate glandular cells High Enhanced Q6YN16 +ENSG00000119471 HSDL2 seminal vesicle glandular cells High Enhanced Q6YN16 +ENSG00000119471 HSDL2 testis cells in seminiferous ducts Medium Enhanced Q6YN16 +ENSG00000119471 HSDL2 testis Leydig cells High Enhanced Q6YN16 +ENSG00000119487 MAPKAP1 epididymis glandular cells Medium Enhanced Q9BPZ7 +ENSG00000119487 MAPKAP1 prostate glandular cells Low Enhanced Q9BPZ7 +ENSG00000119487 MAPKAP1 seminal vesicle glandular cells Medium Enhanced Q9BPZ7 +ENSG00000119487 MAPKAP1 testis cells in seminiferous ducts Medium Enhanced Q9BPZ7 +ENSG00000119487 MAPKAP1 testis Leydig cells Medium Enhanced Q9BPZ7 +ENSG00000119514 GALNT12 epididymis glandular cells High Enhanced Q8IXK2 +ENSG00000119514 GALNT12 prostate glandular cells Medium Enhanced Q8IXK2 +ENSG00000119514 GALNT12 seminal vesicle glandular cells Low Enhanced Q8IXK2 +ENSG00000119514 GALNT12 testis cells in seminiferous ducts Medium Enhanced Q8IXK2 +ENSG00000119514 GALNT12 testis Leydig cells Low Enhanced Q8IXK2 +ENSG00000119535 CSF3R testis Leydig cells Medium Enhanced Q99062 +ENSG00000119655 NPC2 epididymis glandular cells High Enhanced P61916 +ENSG00000119655 NPC2 prostate glandular cells High Enhanced P61916 +ENSG00000119655 NPC2 seminal vesicle glandular cells High Enhanced P61916 +ENSG00000119655 NPC2 testis cells in seminiferous ducts Medium Enhanced P61916 +ENSG00000119655 NPC2 testis Leydig cells High Enhanced P61916 +ENSG00000119673 ACOT2 epididymis glandular cells Medium Enhanced P49753 +ENSG00000119673 ACOT2 prostate glandular cells Medium Enhanced P49753 +ENSG00000119673 ACOT2 seminal vesicle glandular cells High Enhanced P49753 +ENSG00000119673 ACOT2 testis cells in seminiferous ducts High Enhanced P49753 +ENSG00000119673 ACOT2 testis Leydig cells High Enhanced P49753 +ENSG00000119686 FLVCR2 epididymis glandular cells Low Enhanced Q9UPI3 +ENSG00000119686 FLVCR2 testis cells in seminiferous ducts High Enhanced Q9UPI3 +ENSG00000119686 FLVCR2 testis Leydig cells Low Enhanced Q9UPI3 +ENSG00000119689 DLST epididymis glandular cells Medium Supported P36957 +ENSG00000119689 DLST prostate glandular cells Low Supported P36957 +ENSG00000119689 DLST seminal vesicle glandular cells High Supported P36957 +ENSG00000119689 DLST testis cells in seminiferous ducts Medium Supported P36957 +ENSG00000119689 DLST testis Leydig cells Medium Supported P36957 +ENSG00000119703 ZC2HC1C testis cells in seminiferous ducts Medium Enhanced Q53FD0 +ENSG00000119707 RBM25 epididymis glandular cells Medium Supported P49756 +ENSG00000119707 RBM25 prostate glandular cells Medium Supported P49756 +ENSG00000119707 RBM25 seminal vesicle glandular cells Medium Supported P49756 +ENSG00000119707 RBM25 testis cells in seminiferous ducts High Supported P49756 +ENSG00000119707 RBM25 testis Leydig cells Medium Supported P49756 +ENSG00000119711 ALDH6A1 epididymis glandular cells Medium Enhanced Q02252 +ENSG00000119711 ALDH6A1 prostate glandular cells High Enhanced Q02252 +ENSG00000119711 ALDH6A1 seminal vesicle glandular cells High Enhanced Q02252 +ENSG00000119711 ALDH6A1 testis cells in seminiferous ducts High Enhanced Q02252 +ENSG00000119711 ALDH6A1 testis Leydig cells Medium Enhanced Q02252 +ENSG00000119718 EIF2B2 epididymis glandular cells High Enhanced P49770 +ENSG00000119718 EIF2B2 prostate glandular cells High Enhanced P49770 +ENSG00000119718 EIF2B2 seminal vesicle glandular cells High Enhanced P49770 +ENSG00000119718 EIF2B2 testis cells in seminiferous ducts High Enhanced P49770 +ENSG00000119718 EIF2B2 testis Leydig cells Medium Enhanced P49770 +ENSG00000119820 YIPF4 epididymis glandular cells High Supported Q9BSR8 +ENSG00000119820 YIPF4 prostate glandular cells High Supported Q9BSR8 +ENSG00000119820 YIPF4 seminal vesicle glandular cells Medium Supported Q9BSR8 +ENSG00000119820 YIPF4 testis cells in seminiferous ducts Medium Supported Q9BSR8 +ENSG00000119820 YIPF4 testis Leydig cells Medium Supported Q9BSR8 +ENSG00000119866 BCL11A seminal vesicle glandular cells Low Enhanced Q9H165 +ENSG00000119888 EPCAM epididymis glandular cells High Enhanced P16422 +ENSG00000119888 EPCAM seminal vesicle glandular cells High Enhanced P16422 +ENSG00000119965 C10orf88 epididymis glandular cells Medium Enhanced Q9H8K7 +ENSG00000119965 C10orf88 prostate glandular cells Medium Enhanced Q9H8K7 +ENSG00000119965 C10orf88 seminal vesicle glandular cells Medium Enhanced Q9H8K7 +ENSG00000119965 C10orf88 testis cells in seminiferous ducts High Enhanced Q9H8K7 +ENSG00000119965 C10orf88 testis Leydig cells Low Enhanced Q9H8K7 +ENSG00000119969 HELLS testis preleptotene spermatocytes High Enhanced Q9NRZ9 +ENSG00000120053 GOT1 epididymis glandular cells Low Enhanced P17174 +ENSG00000120053 GOT1 seminal vesicle glandular cells Medium Enhanced P17174 +ENSG00000120053 GOT1 testis cells in seminiferous ducts Medium Enhanced P17174 +ENSG00000120053 GOT1 testis Leydig cells Medium Enhanced P17174 +ENSG00000120160 EQTN testis elongated or late spermatids High Enhanced Q9NQ60 +ENSG00000120160 EQTN testis round or early spermatids High Enhanced Q9NQ60 +ENSG00000120210 INSL6 testis elongated or late spermatids Medium Enhanced Q9Y581 +ENSG00000120210 INSL6 testis round or early spermatids High Enhanced Q9Y581 +ENSG00000120253 NUP43 epididymis glandular cells High Enhanced Q8NFH3 +ENSG00000120253 NUP43 prostate glandular cells Medium Enhanced Q8NFH3 +ENSG00000120253 NUP43 seminal vesicle glandular cells High Enhanced Q8NFH3 +ENSG00000120253 NUP43 testis cells in seminiferous ducts Medium Enhanced Q8NFH3 +ENSG00000120253 NUP43 testis Leydig cells High Enhanced Q8NFH3 +ENSG00000120262 CCDC170 testis cells in seminiferous ducts Medium Enhanced Q8IYT3 +ENSG00000120289 MAGEB4 epididymis glandular cells Medium Enhanced O15481 +ENSG00000120289 MAGEB4 testis cells in seminiferous ducts Medium Enhanced O15481 +ENSG00000120341 SEC16B epididymis glandular cells Low Enhanced Q96JE7 +ENSG00000120341 SEC16B testis cells in seminiferous ducts Low Enhanced Q96JE7 +ENSG00000120437 ACAT2 epididymis glandular cells Medium Enhanced Q9BWD1 +ENSG00000120437 ACAT2 prostate glandular cells High Enhanced Q9BWD1 +ENSG00000120437 ACAT2 seminal vesicle glandular cells Medium Enhanced Q9BWD1 +ENSG00000120437 ACAT2 testis cells in seminiferous ducts Medium Enhanced Q9BWD1 +ENSG00000120437 ACAT2 testis Leydig cells High Enhanced Q9BWD1 +ENSG00000120457 KCNJ5 epididymis glandular cells Low Enhanced P48544 +ENSG00000120457 KCNJ5 prostate glandular cells Medium Enhanced P48544 +ENSG00000120457 KCNJ5 seminal vesicle glandular cells Medium Enhanced P48544 +ENSG00000120457 KCNJ5 testis cells in seminiferous ducts Medium Enhanced P48544 +ENSG00000120457 KCNJ5 testis Leydig cells Medium Enhanced P48544 +ENSG00000120658 ENOX1 epididymis glandular cells Low Supported Q8TC92 +ENSG00000120658 ENOX1 prostate glandular cells Low Supported Q8TC92 +ENSG00000120658 ENOX1 seminal vesicle glandular cells Medium Supported Q8TC92 +ENSG00000120658 ENOX1 testis cells in seminiferous ducts Low Supported Q8TC92 +ENSG00000120694 HSPH1 epididymis glandular cells High Enhanced Q92598 +ENSG00000120694 HSPH1 prostate glandular cells High Enhanced Q92598 +ENSG00000120694 HSPH1 seminal vesicle glandular cells Low Enhanced Q92598 +ENSG00000120694 HSPH1 testis cells in seminiferous ducts High Enhanced Q92598 +ENSG00000120694 HSPH1 testis Leydig cells Low Enhanced Q92598 +ENSG00000120725 SIL1 epididymis glandular cells High Enhanced Q9H173 +ENSG00000120725 SIL1 prostate glandular cells Medium Enhanced Q9H173 +ENSG00000120725 SIL1 seminal vesicle glandular cells Medium Enhanced Q9H173 +ENSG00000120725 SIL1 testis cells in seminiferous ducts High Enhanced Q9H173 +ENSG00000120725 SIL1 testis Leydig cells High Enhanced Q9H173 +ENSG00000120733 KDM3B epididymis glandular cells High Supported Q7LBC6 +ENSG00000120733 KDM3B prostate glandular cells High Supported Q7LBC6 +ENSG00000120733 KDM3B seminal vesicle glandular cells High Supported Q7LBC6 +ENSG00000120733 KDM3B testis cells in seminiferous ducts High Supported Q7LBC6 +ENSG00000120733 KDM3B testis Leydig cells Medium Supported Q7LBC6 +ENSG00000120738 EGR1 epididymis glandular cells Medium Enhanced P18146 +ENSG00000120738 EGR1 prostate glandular cells Low Enhanced P18146 +ENSG00000120738 EGR1 seminal vesicle glandular cells Medium Enhanced P18146 +ENSG00000120738 EGR1 testis cells in seminiferous ducts Low Enhanced P18146 +ENSG00000120738 EGR1 testis Leydig cells Medium Enhanced P18146 +ENSG00000120756 PLS1 epididymis glandular cells Medium Enhanced Q14651 +ENSG00000120756 PLS1 seminal vesicle glandular cells Medium Enhanced Q14651 +ENSG00000120756 PLS1 testis cells in seminiferous ducts Medium Enhanced Q14651 +ENSG00000120756 PLS1 testis Leydig cells Medium Enhanced Q14651 +ENSG00000120798 NR2C1 epididymis glandular cells High Enhanced P13056 +ENSG00000120798 NR2C1 prostate glandular cells Medium Enhanced P13056 +ENSG00000120798 NR2C1 seminal vesicle glandular cells Medium Enhanced P13056 +ENSG00000120798 NR2C1 testis cells in seminiferous ducts High Enhanced P13056 +ENSG00000120798 NR2C1 testis Leydig cells Medium Enhanced P13056 +ENSG00000120802 TMPO epididymis glandular cells Medium Enhanced P42166 +ENSG00000120802 TMPO prostate glandular cells High Enhanced P42166 +ENSG00000120802 TMPO seminal vesicle glandular cells Medium Enhanced P42166 +ENSG00000120802 TMPO testis cells in seminiferous ducts Low Enhanced P42166 +ENSG00000120802 TMPO testis Leydig cells Low Enhanced P42166 +ENSG00000120837 NFYB epididymis glandular cells High Supported P25208 +ENSG00000120837 NFYB prostate glandular cells High Supported P25208 +ENSG00000120837 NFYB seminal vesicle glandular cells High Supported P25208 +ENSG00000120837 NFYB testis cells in seminiferous ducts High Supported P25208 +ENSG00000120837 NFYB testis Leydig cells High Supported P25208 +ENSG00000120868 APAF1 epididymis glandular cells Low Enhanced O14727 +ENSG00000120868 APAF1 testis cells in seminiferous ducts Low Enhanced O14727 +ENSG00000120885 CLU epididymis glandular cells High Enhanced P10909 +ENSG00000120885 CLU seminal vesicle glandular cells Low Enhanced P10909 +ENSG00000120885 CLU testis Leydig cells Medium Enhanced P10909 +ENSG00000120948 TARDBP epididymis glandular cells High Supported Q13148 +ENSG00000120948 TARDBP prostate glandular cells High Supported Q13148 +ENSG00000120948 TARDBP testis cells in seminiferous ducts High Supported Q13148 +ENSG00000120948 TARDBP testis Leydig cells High Supported Q13148 +ENSG00000120992 LYPLA1 epididymis glandular cells Low Enhanced O75608 +ENSG00000120992 LYPLA1 prostate glandular cells Low Enhanced O75608 +ENSG00000120992 LYPLA1 seminal vesicle glandular cells Low Enhanced O75608 +ENSG00000120992 LYPLA1 testis cells in seminiferous ducts Low Enhanced O75608 +ENSG00000120992 LYPLA1 testis Leydig cells Low Enhanced O75608 +ENSG00000121022 COPS5 epididymis glandular cells High Supported Q92905 +ENSG00000121022 COPS5 prostate glandular cells High Supported Q92905 +ENSG00000121022 COPS5 seminal vesicle glandular cells High Supported Q92905 +ENSG00000121022 COPS5 testis cells in seminiferous ducts High Supported Q92905 +ENSG00000121022 COPS5 testis Leydig cells High Supported Q92905 +ENSG00000121057 AKAP1 epididymis glandular cells High Supported Q92667 +ENSG00000121057 AKAP1 prostate glandular cells High Supported Q92667 +ENSG00000121057 AKAP1 seminal vesicle glandular cells High Supported Q92667 +ENSG00000121057 AKAP1 testis cells in seminiferous ducts Medium Supported Q92667 +ENSG00000121057 AKAP1 testis Leydig cells Medium Supported Q92667 +ENSG00000121058 COIL epididymis glandular cells Medium Enhanced P38432 +ENSG00000121058 COIL seminal vesicle glandular cells Medium Enhanced P38432 +ENSG00000121058 COIL testis Leydig cells Low Enhanced P38432 +ENSG00000121058 COIL testis pachytene spermatocytes High Enhanced P38432 +ENSG00000121058 COIL testis preleptotene spermatocytes High Enhanced P38432 +ENSG00000121058 COIL testis round or early spermatids High Enhanced P38432 +ENSG00000121058 COIL testis spermatogonia Medium Enhanced P38432 +ENSG00000121101 TEX14 testis cells in seminiferous ducts Medium Enhanced Q8IWB6 +ENSG00000121152 NCAPH testis pachytene spermatocytes Medium Enhanced Q15003 +ENSG00000121152 NCAPH testis preleptotene spermatocytes High Enhanced Q15003 +ENSG00000121152 NCAPH testis round or early spermatids High Enhanced Q15003 +ENSG00000121152 NCAPH testis spermatogonia Medium Enhanced Q15003 +ENSG00000121211 MND1 testis cells in seminiferous ducts Low Enhanced Q9BWT6 +ENSG00000121310 ECHDC2 epididymis glandular cells Medium Enhanced Q86YB7 +ENSG00000121310 ECHDC2 prostate glandular cells Medium Enhanced Q86YB7 +ENSG00000121310 ECHDC2 seminal vesicle glandular cells Low Enhanced Q86YB7 +ENSG00000121310 ECHDC2 testis Leydig cells Low Enhanced Q86YB7 +ENSG00000121380 BCL2L14 testis elongated or late spermatids High Enhanced NA +ENSG00000121380 BCL2L14 testis Leydig cells Low Enhanced NA +ENSG00000121380 BCL2L14 testis round or early spermatids Low Enhanced NA +ENSG00000121380 BCL2L14 testis spermatogonia Low Enhanced NA +ENSG00000121390 PSPC1 epididymis glandular cells Medium Supported Q8WXF1 +ENSG00000121390 PSPC1 prostate glandular cells Medium Supported Q8WXF1 +ENSG00000121390 PSPC1 seminal vesicle glandular cells Medium Supported Q8WXF1 +ENSG00000121390 PSPC1 testis cells in seminiferous ducts High Supported Q8WXF1 +ENSG00000121390 PSPC1 testis Leydig cells Medium Supported Q8WXF1 +ENSG00000121413 ZSCAN18 epididymis glandular cells High Supported Q8TBC5 +ENSG00000121413 ZSCAN18 prostate glandular cells High Supported Q8TBC5 +ENSG00000121413 ZSCAN18 seminal vesicle glandular cells High Supported Q8TBC5 +ENSG00000121413 ZSCAN18 testis cells in seminiferous ducts High Supported Q8TBC5 +ENSG00000121413 ZSCAN18 testis Leydig cells High Supported Q8TBC5 +ENSG00000121552 CSTA prostate glandular cells Low Enhanced P01040 +ENSG00000121570 DPPA4 testis Leydig cells Low Enhanced Q7L190 +ENSG00000121570 DPPA4 testis pachytene spermatocytes Low Enhanced Q7L190 +ENSG00000121570 DPPA4 testis preleptotene spermatocytes Medium Enhanced Q7L190 +ENSG00000121570 DPPA4 testis round or early spermatids Low Enhanced Q7L190 +ENSG00000121570 DPPA4 testis spermatogonia High Enhanced Q7L190 +ENSG00000121671 CRY2 epididymis glandular cells High Supported Q49AN0 +ENSG00000121671 CRY2 prostate glandular cells High Supported Q49AN0 +ENSG00000121671 CRY2 seminal vesicle glandular cells High Supported Q49AN0 +ENSG00000121671 CRY2 testis cells in seminiferous ducts High Supported Q49AN0 +ENSG00000121671 CRY2 testis Leydig cells High Supported Q49AN0 +ENSG00000121691 CAT prostate glandular cells Medium Enhanced P04040 +ENSG00000121691 CAT seminal vesicle glandular cells Low Enhanced P04040 +ENSG00000121749 TBC1D15 epididymis glandular cells High Supported Q8TC07 +ENSG00000121749 TBC1D15 prostate glandular cells High Supported Q8TC07 +ENSG00000121749 TBC1D15 seminal vesicle glandular cells High Supported Q8TC07 +ENSG00000121749 TBC1D15 testis cells in seminiferous ducts High Supported Q8TC07 +ENSG00000121749 TBC1D15 testis Leydig cells High Supported Q8TC07 +ENSG00000121774 KHDRBS1 epididymis glandular cells High Enhanced Q07666 +ENSG00000121774 KHDRBS1 prostate glandular cells High Enhanced Q07666 +ENSG00000121774 KHDRBS1 seminal vesicle glandular cells High Enhanced Q07666 +ENSG00000121774 KHDRBS1 testis cells in seminiferous ducts High Enhanced Q07666 +ENSG00000121774 KHDRBS1 testis Leydig cells High Enhanced Q07666 +ENSG00000121892 PDS5A epididymis glandular cells Medium Enhanced Q29RF7 +ENSG00000121892 PDS5A prostate glandular cells Medium Enhanced Q29RF7 +ENSG00000121892 PDS5A seminal vesicle glandular cells Medium Enhanced Q29RF7 +ENSG00000121892 PDS5A testis cells in seminiferous ducts High Enhanced Q29RF7 +ENSG00000121892 PDS5A testis Leydig cells High Enhanced Q29RF7 +ENSG00000121940 CLCC1 epididymis glandular cells High Enhanced Q96S66 +ENSG00000121940 CLCC1 prostate glandular cells Medium Enhanced Q96S66 +ENSG00000121940 CLCC1 seminal vesicle glandular cells High Enhanced Q96S66 +ENSG00000121940 CLCC1 testis cells in seminiferous ducts Medium Enhanced Q96S66 +ENSG00000121940 CLCC1 testis Leydig cells High Enhanced Q96S66 +ENSG00000122034 GTF3A epididymis glandular cells Low Supported Q92664 +ENSG00000122034 GTF3A prostate glandular cells Low Supported Q92664 +ENSG00000122034 GTF3A seminal vesicle glandular cells Low Supported Q92664 +ENSG00000122034 GTF3A testis cells in seminiferous ducts High Supported Q92664 +ENSG00000122034 GTF3A testis Leydig cells Medium Supported Q92664 +ENSG00000122035 RASL11A epididymis glandular cells Medium Supported Q6T310 +ENSG00000122035 RASL11A prostate glandular cells Medium Supported Q6T310 +ENSG00000122035 RASL11A seminal vesicle glandular cells Medium Supported Q6T310 +ENSG00000122035 RASL11A testis cells in seminiferous ducts Medium Supported Q6T310 +ENSG00000122035 RASL11A testis Leydig cells Medium Supported Q6T310 +ENSG00000122122 SASH3 epididymis glandular cells Low Enhanced O75995 +ENSG00000122122 SASH3 prostate glandular cells Low Enhanced O75995 +ENSG00000122122 SASH3 seminal vesicle glandular cells Low Enhanced O75995 +ENSG00000122122 SASH3 testis cells in seminiferous ducts Low Enhanced O75995 +ENSG00000122194 PLG testis Leydig cells Low Supported P00747 +ENSG00000122218 COPA epididymis glandular cells High Supported P53621 +ENSG00000122218 COPA prostate glandular cells Medium Supported P53621 +ENSG00000122218 COPA seminal vesicle glandular cells High Supported P53621 +ENSG00000122218 COPA testis cells in seminiferous ducts Medium Supported P53621 +ENSG00000122218 COPA testis Leydig cells Medium Supported P53621 +ENSG00000122304 PRM2 testis elongated or late spermatids High Enhanced P04554 +ENSG00000122335 SERAC1 epididymis glandular cells Medium Enhanced Q96JX3 +ENSG00000122335 SERAC1 prostate glandular cells Medium Enhanced Q96JX3 +ENSG00000122335 SERAC1 seminal vesicle glandular cells Medium Enhanced Q96JX3 +ENSG00000122335 SERAC1 testis cells in seminiferous ducts High Enhanced Q96JX3 +ENSG00000122335 SERAC1 testis Leydig cells High Enhanced Q96JX3 +ENSG00000122359 ANXA11 epididymis glandular cells High Supported P50995 +ENSG00000122359 ANXA11 prostate glandular cells High Supported P50995 +ENSG00000122359 ANXA11 seminal vesicle glandular cells Medium Supported P50995 +ENSG00000122359 ANXA11 testis cells in seminiferous ducts Medium Supported P50995 +ENSG00000122359 ANXA11 testis Leydig cells Medium Supported P50995 +ENSG00000122477 LRRC39 testis cells in seminiferous ducts Low Enhanced Q96DD0 +ENSG00000122515 ZMIZ2 epididymis glandular cells Medium Supported Q8NF64 +ENSG00000122515 ZMIZ2 prostate glandular cells Medium Supported Q8NF64 +ENSG00000122515 ZMIZ2 seminal vesicle glandular cells Medium Supported Q8NF64 +ENSG00000122515 ZMIZ2 testis cells in seminiferous ducts Low Supported Q8NF64 +ENSG00000122515 ZMIZ2 testis Leydig cells Medium Supported Q8NF64 +ENSG00000122545 SEPT7 epididymis glandular cells Medium Enhanced Q16181 +ENSG00000122545 SEPT7 prostate glandular cells Medium Enhanced Q16181 +ENSG00000122545 SEPT7 seminal vesicle glandular cells Medium Enhanced Q16181 +ENSG00000122545 SEPT7 testis cells in seminiferous ducts Medium Enhanced Q16181 +ENSG00000122545 SEPT7 testis Leydig cells Low Enhanced Q16181 +ENSG00000122565 CBX3 epididymis glandular cells Medium Enhanced Q13185 +ENSG00000122565 CBX3 prostate glandular cells Medium Enhanced Q13185 +ENSG00000122565 CBX3 seminal vesicle glandular cells Medium Enhanced Q13185 +ENSG00000122565 CBX3 testis cells in seminiferous ducts Medium Enhanced Q13185 +ENSG00000122565 CBX3 testis Leydig cells Medium Enhanced Q13185 +ENSG00000122566 HNRNPA2B1 epididymis glandular cells High Supported P22626 +ENSG00000122566 HNRNPA2B1 prostate glandular cells High Supported P22626 +ENSG00000122566 HNRNPA2B1 seminal vesicle glandular cells High Supported P22626 +ENSG00000122566 HNRNPA2B1 testis cells in seminiferous ducts High Supported P22626 +ENSG00000122566 HNRNPA2B1 testis Leydig cells High Supported P22626 +ENSG00000122585 NPY epididymis glandular cells Low Supported P01303 +ENSG00000122585 NPY prostate glandular cells Medium Supported P01303 +ENSG00000122692 SMU1 epididymis glandular cells Medium Supported Q2TAY7 +ENSG00000122692 SMU1 prostate glandular cells Low Supported Q2TAY7 +ENSG00000122692 SMU1 seminal vesicle glandular cells Low Supported Q2TAY7 +ENSG00000122692 SMU1 testis cells in seminiferous ducts Medium Supported Q2TAY7 +ENSG00000122692 SMU1 testis Leydig cells Medium Supported Q2TAY7 +ENSG00000122705 CLTA epididymis glandular cells High Enhanced P09496 +ENSG00000122705 CLTA prostate glandular cells Medium Enhanced P09496 +ENSG00000122705 CLTA seminal vesicle glandular cells Medium Enhanced P09496 +ENSG00000122705 CLTA testis cells in seminiferous ducts High Enhanced P09496 +ENSG00000122705 CLTA testis Leydig cells Medium Enhanced P09496 +ENSG00000122707 RECK testis cells in seminiferous ducts Low Supported O95980 +ENSG00000122729 ACO1 epididymis glandular cells Medium Enhanced P21399 +ENSG00000122729 ACO1 prostate glandular cells Medium Enhanced P21399 +ENSG00000122729 ACO1 testis cells in seminiferous ducts Medium Enhanced P21399 +ENSG00000122729 ACO1 testis Leydig cells Medium Enhanced P21399 +ENSG00000122735 DNAI1 testis elongated or late spermatids High Enhanced Q9UI46 +ENSG00000122735 DNAI1 testis pachytene spermatocytes High Enhanced Q9UI46 +ENSG00000122735 DNAI1 testis preleptotene spermatocytes Medium Enhanced Q9UI46 +ENSG00000122735 DNAI1 testis round or early spermatids High Enhanced Q9UI46 +ENSG00000122735 DNAI1 testis spermatogonia Medium Enhanced Q9UI46 +ENSG00000122786 CALD1 epididymis glandular cells Low Enhanced Q05682 +ENSG00000122786 CALD1 prostate glandular cells Low Enhanced Q05682 +ENSG00000122786 CALD1 testis cells in seminiferous ducts Low Enhanced Q05682 +ENSG00000122786 CALD1 testis Leydig cells Low Enhanced Q05682 +ENSG00000122863 CHST3 seminal vesicle glandular cells Medium Enhanced Q7LGC8 +ENSG00000122863 CHST3 testis cells in seminiferous ducts Medium Enhanced Q7LGC8 +ENSG00000122863 CHST3 testis Leydig cells Medium Enhanced Q7LGC8 +ENSG00000122870 BICC1 epididymis glandular cells Low Enhanced Q9H694 +ENSG00000122870 BICC1 prostate glandular cells High Enhanced Q9H694 +ENSG00000122870 BICC1 seminal vesicle glandular cells High Enhanced Q9H694 +ENSG00000122870 BICC1 testis cells in seminiferous ducts Medium Enhanced Q9H694 +ENSG00000122870 BICC1 testis Leydig cells High Enhanced Q9H694 +ENSG00000122884 P4HA1 epididymis glandular cells Medium Enhanced P13674 +ENSG00000122884 P4HA1 prostate glandular cells Medium Enhanced P13674 +ENSG00000122884 P4HA1 testis cells in seminiferous ducts High Enhanced P13674 +ENSG00000122884 P4HA1 testis Leydig cells High Enhanced P13674 +ENSG00000122952 ZWINT epididymis glandular cells Medium Enhanced O95229 +ENSG00000122952 ZWINT prostate glandular cells Medium Enhanced O95229 +ENSG00000122952 ZWINT testis cells in seminiferous ducts High Enhanced O95229 +ENSG00000122952 ZWINT testis Leydig cells Medium Enhanced O95229 +ENSG00000122958 VPS26A epididymis glandular cells Medium Enhanced O75436 +ENSG00000122958 VPS26A prostate glandular cells Medium Enhanced O75436 +ENSG00000122958 VPS26A seminal vesicle glandular cells Medium Enhanced O75436 +ENSG00000122958 VPS26A testis cells in seminiferous ducts High Enhanced O75436 +ENSG00000122958 VPS26A testis Leydig cells Low Enhanced O75436 +ENSG00000122965 RBM19 epididymis glandular cells Medium Supported Q9Y4C8 +ENSG00000122965 RBM19 prostate glandular cells Medium Supported Q9Y4C8 +ENSG00000122965 RBM19 testis cells in seminiferous ducts Medium Supported Q9Y4C8 +ENSG00000122965 RBM19 testis Leydig cells Medium Supported Q9Y4C8 +ENSG00000122970 IFT81 prostate glandular cells Low Enhanced Q8WYA0 +ENSG00000122970 IFT81 seminal vesicle glandular cells Medium Enhanced Q8WYA0 +ENSG00000122970 IFT81 testis cells in seminiferous ducts High Enhanced Q8WYA0 +ENSG00000122970 IFT81 testis Leydig cells Medium Enhanced Q8WYA0 +ENSG00000122971 ACADS epididymis glandular cells Medium Enhanced P16219 +ENSG00000122971 ACADS prostate glandular cells Medium Enhanced P16219 +ENSG00000122971 ACADS seminal vesicle glandular cells Medium Enhanced P16219 +ENSG00000122971 ACADS testis cells in seminiferous ducts Medium Enhanced P16219 +ENSG00000122971 ACADS testis Leydig cells Medium Enhanced P16219 +ENSG00000122986 HVCN1 testis cells in seminiferous ducts Medium Enhanced Q96D96 +ENSG00000123130 ACOT9 epididymis glandular cells Low Supported Q9Y305 +ENSG00000123130 ACOT9 prostate glandular cells Medium Supported Q9Y305 +ENSG00000123130 ACOT9 seminal vesicle glandular cells Medium Supported Q9Y305 +ENSG00000123130 ACOT9 testis cells in seminiferous ducts Medium Supported Q9Y305 +ENSG00000123130 ACOT9 testis Leydig cells High Supported Q9Y305 +ENSG00000123131 PRDX4 epididymis glandular cells Medium Enhanced Q13162 +ENSG00000123131 PRDX4 prostate glandular cells Low Enhanced Q13162 +ENSG00000123131 PRDX4 seminal vesicle glandular cells Medium Enhanced Q13162 +ENSG00000123131 PRDX4 testis cells in seminiferous ducts Medium Enhanced Q13162 +ENSG00000123131 PRDX4 testis Leydig cells High Enhanced Q13162 +ENSG00000123165 ACTRT1 testis elongated or late spermatids Medium Supported Q8TDG2 +ENSG00000123165 ACTRT1 testis Leydig cells Low Supported Q8TDG2 +ENSG00000123165 ACTRT1 testis round or early spermatids High Supported Q8TDG2 +ENSG00000123191 ATP7B epididymis glandular cells Medium Supported P35670 +ENSG00000123191 ATP7B prostate glandular cells Low Supported P35670 +ENSG00000123191 ATP7B seminal vesicle glandular cells Medium Supported P35670 +ENSG00000123191 ATP7B testis cells in seminiferous ducts Low Supported P35670 +ENSG00000123191 ATP7B testis Leydig cells High Supported P35670 +ENSG00000123240 OPTN epididymis glandular cells Medium Supported Q96CV9 +ENSG00000123240 OPTN prostate glandular cells High Supported Q96CV9 +ENSG00000123240 OPTN seminal vesicle glandular cells High Supported Q96CV9 +ENSG00000123240 OPTN testis cells in seminiferous ducts High Supported Q96CV9 +ENSG00000123240 OPTN testis Leydig cells High Supported Q96CV9 +ENSG00000123268 ATF1 epididymis glandular cells High Enhanced P18846 +ENSG00000123268 ATF1 prostate glandular cells Medium Enhanced P18846 +ENSG00000123268 ATF1 seminal vesicle glandular cells Medium Enhanced P18846 +ENSG00000123268 ATF1 testis cells in seminiferous ducts High Enhanced P18846 +ENSG00000123268 ATF1 testis Leydig cells Medium Enhanced P18846 +ENSG00000123307 NEUROD4 testis Leydig cells High Supported Q9HD90 +ENSG00000123374 CDK2 epididymis glandular cells Low Enhanced P24941 +ENSG00000123374 CDK2 prostate glandular cells Low Enhanced P24941 +ENSG00000123374 CDK2 testis cells in seminiferous ducts Low Enhanced P24941 +ENSG00000123374 CDK2 testis Leydig cells Low Enhanced P24941 +ENSG00000123384 LRP1 testis Leydig cells Medium Supported Q07954 +ENSG00000123416 TUBA1B epididymis glandular cells High Enhanced P68363 +ENSG00000123416 TUBA1B prostate glandular cells High Enhanced P68363 +ENSG00000123416 TUBA1B seminal vesicle glandular cells High Enhanced P68363 +ENSG00000123416 TUBA1B testis cells in seminiferous ducts High Enhanced P68363 +ENSG00000123416 TUBA1B testis Leydig cells Medium Enhanced P68363 +ENSG00000123562 MORF4L2 epididymis glandular cells High Supported Q15014 +ENSG00000123562 MORF4L2 prostate glandular cells High Supported Q15014 +ENSG00000123562 MORF4L2 seminal vesicle glandular cells High Supported Q15014 +ENSG00000123562 MORF4L2 testis cells in seminiferous ducts High Supported Q15014 +ENSG00000123562 MORF4L2 testis Leydig cells High Supported Q15014 +ENSG00000123570 RAB9B epididymis glandular cells Medium Enhanced Q9NP90 +ENSG00000123570 RAB9B prostate glandular cells Low Enhanced Q9NP90 +ENSG00000123570 RAB9B seminal vesicle glandular cells Low Enhanced Q9NP90 +ENSG00000123570 RAB9B testis cells in seminiferous ducts Medium Enhanced Q9NP90 +ENSG00000123570 RAB9B testis Leydig cells Low Enhanced Q9NP90 +ENSG00000123576 ESX1 testis pachytene spermatocytes Low Enhanced Q8N693 +ENSG00000123576 ESX1 testis preleptotene spermatocytes Medium Enhanced Q8N693 +ENSG00000123576 ESX1 testis round or early spermatids Low Enhanced Q8N693 +ENSG00000123576 ESX1 testis spermatogonia High Enhanced Q8N693 +ENSG00000123595 RAB9A epididymis glandular cells High Enhanced P51151 +ENSG00000123595 RAB9A prostate glandular cells Medium Enhanced P51151 +ENSG00000123595 RAB9A seminal vesicle glandular cells Medium Enhanced P51151 +ENSG00000123595 RAB9A testis cells in seminiferous ducts Medium Enhanced P51151 +ENSG00000123595 RAB9A testis Leydig cells High Enhanced P51151 +ENSG00000123810 B9D2 epididymis glandular cells Low Enhanced Q9BPU9 +ENSG00000123810 B9D2 seminal vesicle glandular cells Low Enhanced Q9BPU9 +ENSG00000123810 B9D2 testis cells in seminiferous ducts Low Enhanced Q9BPU9 +ENSG00000123810 B9D2 testis Leydig cells Low Enhanced Q9BPU9 +ENSG00000123815 COQ8B epididymis glandular cells Medium Enhanced Q96D53 +ENSG00000123815 COQ8B prostate glandular cells High Enhanced Q96D53 +ENSG00000123815 COQ8B seminal vesicle glandular cells High Enhanced Q96D53 +ENSG00000123815 COQ8B testis cells in seminiferous ducts High Enhanced Q96D53 +ENSG00000123815 COQ8B testis Leydig cells High Enhanced Q96D53 +ENSG00000123992 DNPEP epididymis glandular cells Medium Enhanced Q9ULA0 +ENSG00000123992 DNPEP prostate glandular cells High Enhanced Q9ULA0 +ENSG00000123992 DNPEP seminal vesicle glandular cells High Enhanced Q9ULA0 +ENSG00000123992 DNPEP testis cells in seminiferous ducts Medium Enhanced Q9ULA0 +ENSG00000123992 DNPEP testis Leydig cells High Enhanced Q9ULA0 +ENSG00000123999 INHA testis Leydig cells High Enhanced P05111 +ENSG00000123999 INHA testis sertoli cells High Enhanced P05111 +ENSG00000124092 CTCFL testis Leydig cells Low Enhanced Q8NI51 +ENSG00000124092 CTCFL testis pachytene spermatocytes Low Enhanced Q8NI51 +ENSG00000124092 CTCFL testis preleptotene spermatocytes High Enhanced Q8NI51 +ENSG00000124092 CTCFL testis round or early spermatids Low Enhanced Q8NI51 +ENSG00000124092 CTCFL testis spermatogonia Medium Enhanced Q8NI51 +ENSG00000124107 SLPI seminal vesicle glandular cells Medium Enhanced P03973 +ENSG00000124145 SDC4 epididymis glandular cells Medium Supported P31431 +ENSG00000124145 SDC4 prostate glandular cells High Supported P31431 +ENSG00000124145 SDC4 seminal vesicle glandular cells Medium Supported P31431 +ENSG00000124145 SDC4 testis cells in seminiferous ducts High Supported P31431 +ENSG00000124145 SDC4 testis Leydig cells Medium Supported P31431 +ENSG00000124151 NCOA3 epididymis glandular cells Medium Supported Q9Y6Q9 +ENSG00000124151 NCOA3 prostate glandular cells Medium Supported Q9Y6Q9 +ENSG00000124151 NCOA3 seminal vesicle glandular cells Medium Supported Q9Y6Q9 +ENSG00000124151 NCOA3 testis cells in seminiferous ducts Medium Supported Q9Y6Q9 +ENSG00000124151 NCOA3 testis Leydig cells Medium Supported Q9Y6Q9 +ENSG00000124157 SEMG2 epididymis glandular cells Low Enhanced Q02383 +ENSG00000124157 SEMG2 seminal vesicle glandular cells High Enhanced Q02383 +ENSG00000124164 VAPB epididymis glandular cells High Supported O95292 +ENSG00000124164 VAPB prostate glandular cells Medium Supported O95292 +ENSG00000124164 VAPB seminal vesicle glandular cells Medium Supported O95292 +ENSG00000124164 VAPB testis cells in seminiferous ducts Medium Supported O95292 +ENSG00000124164 VAPB testis Leydig cells High Supported O95292 +ENSG00000124193 SRSF6 epididymis glandular cells High Supported Q13247 +ENSG00000124193 SRSF6 prostate glandular cells High Supported Q13247 +ENSG00000124193 SRSF6 seminal vesicle glandular cells High Supported Q13247 +ENSG00000124193 SRSF6 testis cells in seminiferous ducts High Supported Q13247 +ENSG00000124193 SRSF6 testis Leydig cells High Supported Q13247 +ENSG00000124196 GTSF1L epididymis glandular cells Low Enhanced Q9H1H1 +ENSG00000124196 GTSF1L testis elongated or late spermatids High Enhanced Q9H1H1 +ENSG00000124196 GTSF1L testis peritubular cells Low Enhanced Q9H1H1 +ENSG00000124196 GTSF1L testis round or early spermatids High Enhanced Q9H1H1 +ENSG00000124198 ARFGEF2 epididymis glandular cells Medium Supported Q9Y6D5 +ENSG00000124198 ARFGEF2 prostate glandular cells Medium Supported Q9Y6D5 +ENSG00000124198 ARFGEF2 seminal vesicle glandular cells Medium Supported Q9Y6D5 +ENSG00000124198 ARFGEF2 testis cells in seminiferous ducts Medium Supported Q9Y6D5 +ENSG00000124198 ARFGEF2 testis Leydig cells Medium Supported Q9Y6D5 +ENSG00000124207 CSE1L testis cells in seminiferous ducts High Enhanced P55060 +ENSG00000124212 PTGIS epididymis glandular cells Low Enhanced Q16647 +ENSG00000124212 PTGIS prostate glandular cells Low Enhanced Q16647 +ENSG00000124212 PTGIS seminal vesicle glandular cells Medium Enhanced Q16647 +ENSG00000124212 PTGIS testis cells in seminiferous ducts Low Enhanced Q16647 +ENSG00000124212 PTGIS testis Leydig cells Medium Enhanced Q16647 +ENSG00000124216 SNAI1 epididymis glandular cells High Supported O95863 +ENSG00000124216 SNAI1 prostate glandular cells High Supported O95863 +ENSG00000124216 SNAI1 seminal vesicle glandular cells High Supported O95863 +ENSG00000124216 SNAI1 testis cells in seminiferous ducts High Supported O95863 +ENSG00000124216 SNAI1 testis Leydig cells Medium Supported O95863 +ENSG00000124233 SEMG1 seminal vesicle glandular cells High Enhanced P04279 +ENSG00000124237 C20orf85 testis cells in seminiferous ducts Low Enhanced Q9H1P6 +ENSG00000124251 TP53TG5 testis elongated or late spermatids Medium Enhanced Q9Y2B4 +ENSG00000124251 TP53TG5 testis Leydig cells Low Enhanced Q9Y2B4 +ENSG00000124251 TP53TG5 testis pachytene spermatocytes Medium Enhanced Q9Y2B4 +ENSG00000124251 TP53TG5 testis preleptotene spermatocytes High Enhanced Q9Y2B4 +ENSG00000124251 TP53TG5 testis round or early spermatids Medium Enhanced Q9Y2B4 +ENSG00000124251 TP53TG5 testis spermatogonia High Enhanced Q9Y2B4 +ENSG00000124275 MTRR epididymis glandular cells Medium Supported Q9UBK8 +ENSG00000124275 MTRR prostate glandular cells Medium Supported Q9UBK8 +ENSG00000124275 MTRR seminal vesicle glandular cells Medium Supported Q9UBK8 +ENSG00000124275 MTRR testis cells in seminiferous ducts Medium Supported Q9UBK8 +ENSG00000124275 MTRR testis Leydig cells Medium Supported Q9UBK8 +ENSG00000124357 NAGK epididymis glandular cells Low Enhanced Q9UJ70 +ENSG00000124357 NAGK prostate glandular cells Low Enhanced Q9UJ70 +ENSG00000124357 NAGK seminal vesicle glandular cells Low Enhanced Q9UJ70 +ENSG00000124357 NAGK testis cells in seminiferous ducts Low Enhanced Q9UJ70 +ENSG00000124357 NAGK testis Leydig cells Low Enhanced Q9UJ70 +ENSG00000124383 MPHOSPH10 epididymis glandular cells Low Enhanced O00566 +ENSG00000124383 MPHOSPH10 prostate glandular cells High Enhanced O00566 +ENSG00000124383 MPHOSPH10 testis cells in seminiferous ducts Low Enhanced O00566 +ENSG00000124383 MPHOSPH10 testis Leydig cells Medium Enhanced O00566 +ENSG00000124406 ATP8A1 epididymis glandular cells Medium Enhanced Q9Y2Q0 +ENSG00000124406 ATP8A1 prostate glandular cells Medium Enhanced Q9Y2Q0 +ENSG00000124406 ATP8A1 seminal vesicle glandular cells Medium Enhanced Q9Y2Q0 +ENSG00000124406 ATP8A1 testis cells in seminiferous ducts Medium Enhanced Q9Y2Q0 +ENSG00000124406 ATP8A1 testis Leydig cells Medium Enhanced Q9Y2Q0 +ENSG00000124422 USP22 epididymis glandular cells High Supported Q9UPT9 +ENSG00000124422 USP22 prostate glandular cells High Supported Q9UPT9 +ENSG00000124422 USP22 seminal vesicle glandular cells Medium Supported Q9UPT9 +ENSG00000124422 USP22 testis cells in seminiferous ducts High Supported Q9UPT9 +ENSG00000124422 USP22 testis Leydig cells Medium Supported Q9UPT9 +ENSG00000124449 IRGC testis elongated or late spermatids High Enhanced Q6NXR0 +ENSG00000124449 IRGC testis Leydig cells Low Enhanced Q6NXR0 +ENSG00000124449 IRGC testis preleptotene spermatocytes Low Enhanced Q6NXR0 +ENSG00000124449 IRGC testis round or early spermatids Medium Enhanced Q6NXR0 +ENSG00000124449 IRGC testis spermatogonia Low Enhanced Q6NXR0 +ENSG00000124490 CRISP2 testis elongated or late spermatids High Enhanced P16562 +ENSG00000124490 CRISP2 testis pachytene spermatocytes High Enhanced P16562 +ENSG00000124490 CRISP2 testis preleptotene spermatocytes High Enhanced P16562 +ENSG00000124490 CRISP2 testis round or early spermatids High Enhanced P16562 +ENSG00000124490 CRISP2 testis spermatogonia High Enhanced P16562 +ENSG00000124491 F13A1 testis Leydig cells Low Enhanced P00488 +ENSG00000124496 TRERF1 epididymis glandular cells Low Enhanced Q96PN7 +ENSG00000124496 TRERF1 prostate glandular cells Low Enhanced Q96PN7 +ENSG00000124496 TRERF1 seminal vesicle glandular cells Low Enhanced Q96PN7 +ENSG00000124496 TRERF1 testis cells in seminiferous ducts High Enhanced Q96PN7 +ENSG00000124496 TRERF1 testis Leydig cells Low Enhanced Q96PN7 +ENSG00000124535 WRNIP1 epididymis glandular cells High Enhanced Q96S55 +ENSG00000124535 WRNIP1 prostate glandular cells Medium Enhanced Q96S55 +ENSG00000124535 WRNIP1 seminal vesicle glandular cells High Enhanced Q96S55 +ENSG00000124535 WRNIP1 testis cells in seminiferous ducts High Enhanced Q96S55 +ENSG00000124535 WRNIP1 testis Leydig cells Medium Enhanced Q96S55 +ENSG00000124562 SNRPC epididymis glandular cells High Supported P09234 +ENSG00000124562 SNRPC prostate glandular cells High Supported P09234 +ENSG00000124562 SNRPC seminal vesicle glandular cells High Supported P09234 +ENSG00000124562 SNRPC testis cells in seminiferous ducts High Supported P09234 +ENSG00000124562 SNRPC testis Leydig cells High Supported P09234 +ENSG00000124570 SERPINB6 epididymis glandular cells High Enhanced P35237 +ENSG00000124570 SERPINB6 prostate glandular cells High Enhanced P35237 +ENSG00000124570 SERPINB6 seminal vesicle glandular cells Medium Enhanced P35237 +ENSG00000124570 SERPINB6 testis cells in seminiferous ducts High Enhanced P35237 +ENSG00000124570 SERPINB6 testis Leydig cells High Enhanced P35237 +ENSG00000124571 XPO5 epididymis glandular cells Medium Enhanced Q9HAV4 +ENSG00000124571 XPO5 prostate glandular cells Low Enhanced Q9HAV4 +ENSG00000124571 XPO5 testis cells in seminiferous ducts High Enhanced Q9HAV4 +ENSG00000124571 XPO5 testis Leydig cells Medium Enhanced Q9HAV4 +ENSG00000124587 PEX6 epididymis glandular cells Medium Enhanced Q13608 +ENSG00000124587 PEX6 prostate glandular cells Medium Enhanced Q13608 +ENSG00000124587 PEX6 seminal vesicle glandular cells Low Enhanced Q13608 +ENSG00000124587 PEX6 testis cells in seminiferous ducts Medium Enhanced Q13608 +ENSG00000124588 NQO2 epididymis glandular cells Low Enhanced P16083 +ENSG00000124588 NQO2 prostate glandular cells Low Enhanced P16083 +ENSG00000124588 NQO2 seminal vesicle glandular cells Low Enhanced P16083 +ENSG00000124588 NQO2 testis Leydig cells Medium Enhanced P16083 +ENSG00000124602 UNC5CL epididymis glandular cells Low Enhanced Q8IV45 +ENSG00000124602 UNC5CL prostate glandular cells Low Enhanced Q8IV45 +ENSG00000124602 UNC5CL seminal vesicle glandular cells Low Enhanced Q8IV45 +ENSG00000124610 HIST1H1A epididymis glandular cells High Supported Q02539 +ENSG00000124610 HIST1H1A prostate glandular cells Medium Supported Q02539 +ENSG00000124610 HIST1H1A seminal vesicle glandular cells High Supported Q02539 +ENSG00000124610 HIST1H1A testis cells in seminiferous ducts High Supported Q02539 +ENSG00000124610 HIST1H1A testis Leydig cells Medium Supported Q02539 +ENSG00000124635 HIST1H2BJ epididymis glandular cells High Supported P06899 +ENSG00000124635 HIST1H2BJ prostate glandular cells High Supported P06899 +ENSG00000124635 HIST1H2BJ seminal vesicle glandular cells High Supported P06899 +ENSG00000124635 HIST1H2BJ testis Leydig cells High Supported P06899 +ENSG00000124635 HIST1H2BJ testis pachytene spermatocytes Medium Supported P06899 +ENSG00000124635 HIST1H2BJ testis peritubular cells High Supported P06899 +ENSG00000124635 HIST1H2BJ testis preleptotene spermatocytes High Supported P06899 +ENSG00000124635 HIST1H2BJ testis round or early spermatids Low Supported P06899 +ENSG00000124635 HIST1H2BJ testis sertoli cells Medium Supported P06899 +ENSG00000124635 HIST1H2BJ testis spermatogonia High Supported P06899 +ENSG00000124678 TCP11 testis elongated or late spermatids High Supported Q8WWU5 +ENSG00000124678 TCP11 testis round or early spermatids Medium Supported Q8WWU5 +ENSG00000124713 GNMT prostate glandular cells Low Enhanced Q14749 +ENSG00000124762 CDKN1A epididymis glandular cells Medium Supported P38936 +ENSG00000124762 CDKN1A prostate glandular cells Low Supported P38936 +ENSG00000124762 CDKN1A seminal vesicle glandular cells Low Supported P38936 +ENSG00000124762 CDKN1A testis Leydig cells High Supported P38936 +ENSG00000124767 GLO1 epididymis glandular cells High Enhanced Q04760 +ENSG00000124767 GLO1 prostate glandular cells High Enhanced Q04760 +ENSG00000124767 GLO1 seminal vesicle glandular cells Medium Enhanced Q04760 +ENSG00000124767 GLO1 testis cells in seminiferous ducts Low Enhanced Q04760 +ENSG00000124767 GLO1 testis Leydig cells High Enhanced Q04760 +ENSG00000124783 SSR1 epididymis glandular cells High Enhanced P43307 +ENSG00000124783 SSR1 prostate glandular cells Low Enhanced P43307 +ENSG00000124783 SSR1 seminal vesicle glandular cells Medium Enhanced P43307 +ENSG00000124783 SSR1 testis cells in seminiferous ducts Low Enhanced P43307 +ENSG00000124783 SSR1 testis Leydig cells Medium Enhanced P43307 +ENSG00000124784 RIOK1 epididymis glandular cells Low Enhanced Q9BRS2 +ENSG00000124784 RIOK1 seminal vesicle glandular cells Low Enhanced Q9BRS2 +ENSG00000124784 RIOK1 testis cells in seminiferous ducts High Enhanced Q9BRS2 +ENSG00000124784 RIOK1 testis Leydig cells Low Enhanced Q9BRS2 +ENSG00000124789 NUP153 epididymis glandular cells High Enhanced P49790 +ENSG00000124789 NUP153 prostate glandular cells Medium Enhanced P49790 +ENSG00000124789 NUP153 seminal vesicle glandular cells High Enhanced P49790 +ENSG00000124789 NUP153 testis cells in seminiferous ducts Medium Enhanced P49790 +ENSG00000124789 NUP153 testis Leydig cells Medium Enhanced P49790 +ENSG00000124795 DEK epididymis glandular cells Medium Enhanced P35659 +ENSG00000124795 DEK prostate glandular cells Medium Enhanced P35659 +ENSG00000124795 DEK seminal vesicle glandular cells Low Enhanced P35659 +ENSG00000124795 DEK testis cells in seminiferous ducts Medium Enhanced P35659 +ENSG00000124795 DEK testis Leydig cells Medium Enhanced P35659 +ENSG00000124812 CRISP1 epididymis glandular cells High Enhanced P54107 +ENSG00000124939 SCGB2A1 epididymis glandular cells High Enhanced O75556 +ENSG00000125166 GOT2 epididymis glandular cells High Enhanced P00505 +ENSG00000125166 GOT2 prostate glandular cells Medium Enhanced P00505 +ENSG00000125166 GOT2 seminal vesicle glandular cells High Enhanced P00505 +ENSG00000125166 GOT2 testis cells in seminiferous ducts Medium Enhanced P00505 +ENSG00000125166 GOT2 testis Leydig cells High Enhanced P00505 +ENSG00000125170 DOK4 epididymis glandular cells High Supported Q8TEW6 +ENSG00000125170 DOK4 seminal vesicle glandular cells Medium Supported Q8TEW6 +ENSG00000125170 DOK4 testis cells in seminiferous ducts Medium Supported Q8TEW6 +ENSG00000125170 DOK4 testis Leydig cells Medium Supported Q8TEW6 +ENSG00000125207 PIWIL1 testis elongated or late spermatids Medium Enhanced NA +ENSG00000125207 PIWIL1 testis Leydig cells Medium Enhanced NA +ENSG00000125207 PIWIL1 testis pachytene spermatocytes High Enhanced NA +ENSG00000125207 PIWIL1 testis peritubular cells Low Enhanced NA +ENSG00000125207 PIWIL1 testis preleptotene spermatocytes Medium Enhanced NA +ENSG00000125207 PIWIL1 testis round or early spermatids High Enhanced NA +ENSG00000125207 PIWIL1 testis spermatogonia Low Enhanced NA +ENSG00000125246 CLYBL epididymis glandular cells High Enhanced Q8N0X4 +ENSG00000125246 CLYBL prostate glandular cells High Enhanced Q8N0X4 +ENSG00000125246 CLYBL seminal vesicle glandular cells High Enhanced Q8N0X4 +ENSG00000125246 CLYBL testis cells in seminiferous ducts High Enhanced Q8N0X4 +ENSG00000125246 CLYBL testis Leydig cells High Enhanced Q8N0X4 +ENSG00000125257 ABCC4 prostate glandular cells Medium Enhanced O15439 +ENSG00000125266 EFNB2 epididymis glandular cells Medium Supported P52799 +ENSG00000125266 EFNB2 prostate glandular cells Medium Supported P52799 +ENSG00000125266 EFNB2 seminal vesicle glandular cells Medium Supported P52799 +ENSG00000125266 EFNB2 testis cells in seminiferous ducts Low Supported P52799 +ENSG00000125266 EFNB2 testis Leydig cells Medium Supported P52799 +ENSG00000125304 TM9SF2 epididymis glandular cells High Supported Q99805 +ENSG00000125304 TM9SF2 prostate glandular cells High Supported Q99805 +ENSG00000125304 TM9SF2 seminal vesicle glandular cells High Supported Q99805 +ENSG00000125304 TM9SF2 testis cells in seminiferous ducts High Supported Q99805 +ENSG00000125304 TM9SF2 testis Leydig cells Medium Supported Q99805 +ENSG00000125347 IRF1 epididymis glandular cells Medium Supported P10914 +ENSG00000125347 IRF1 seminal vesicle glandular cells Medium Supported P10914 +ENSG00000125347 IRF1 testis cells in seminiferous ducts Medium Supported P10914 +ENSG00000125347 IRF1 testis Leydig cells Medium Supported P10914 +ENSG00000125354 SEPT6 epididymis glandular cells Medium Supported Q14141 +ENSG00000125354 SEPT6 prostate glandular cells Medium Supported Q14141 +ENSG00000125354 SEPT6 testis cells in seminiferous ducts Low Supported Q14141 +ENSG00000125354 SEPT6 testis Leydig cells Medium Supported Q14141 +ENSG00000125356 NDUFA1 epididymis glandular cells Low Enhanced O15239 +ENSG00000125356 NDUFA1 prostate glandular cells Medium Enhanced O15239 +ENSG00000125356 NDUFA1 seminal vesicle glandular cells High Enhanced O15239 +ENSG00000125356 NDUFA1 testis cells in seminiferous ducts Low Enhanced O15239 +ENSG00000125356 NDUFA1 testis Leydig cells Medium Enhanced O15239 +ENSG00000125378 BMP4 epididymis glandular cells Medium Enhanced P12644 +ENSG00000125378 BMP4 testis cells in seminiferous ducts Low Enhanced P12644 +ENSG00000125378 BMP4 testis Leydig cells Low Enhanced P12644 +ENSG00000125398 SOX9 epididymis glandular cells Medium Enhanced P48436 +ENSG00000125398 SOX9 prostate glandular cells High Enhanced P48436 +ENSG00000125398 SOX9 seminal vesicle glandular cells Medium Enhanced P48436 +ENSG00000125398 SOX9 testis cells in seminiferous ducts Medium Enhanced P48436 +ENSG00000125414 MYH2 epididymis glandular cells Low Enhanced Q9UKX2 +ENSG00000125445 MRPS7 epididymis glandular cells Medium Supported Q9Y2R9 +ENSG00000125445 MRPS7 prostate glandular cells Medium Supported Q9Y2R9 +ENSG00000125445 MRPS7 seminal vesicle glandular cells Medium Supported Q9Y2R9 +ENSG00000125445 MRPS7 testis cells in seminiferous ducts Medium Supported Q9Y2R9 +ENSG00000125445 MRPS7 testis Leydig cells Medium Supported Q9Y2R9 +ENSG00000125450 NUP85 epididymis glandular cells Medium Enhanced Q9BW27 +ENSG00000125450 NUP85 seminal vesicle glandular cells Low Enhanced Q9BW27 +ENSG00000125450 NUP85 testis cells in seminiferous ducts Medium Enhanced Q9BW27 +ENSG00000125450 NUP85 testis Leydig cells Medium Enhanced Q9BW27 +ENSG00000125482 TTF1 epididymis glandular cells High Supported Q15361 +ENSG00000125482 TTF1 prostate glandular cells High Supported Q15361 +ENSG00000125482 TTF1 seminal vesicle glandular cells Medium Supported Q15361 +ENSG00000125482 TTF1 testis cells in seminiferous ducts High Supported Q15361 +ENSG00000125482 TTF1 testis Leydig cells High Supported Q15361 +ENSG00000125618 PAX8 epididymis glandular cells High Enhanced Q06710 +ENSG00000125618 PAX8 seminal vesicle glandular cells Medium Enhanced Q06710 +ENSG00000125637 PSD4 epididymis glandular cells Low Enhanced Q8NDX1 +ENSG00000125637 PSD4 prostate glandular cells Medium Enhanced Q8NDX1 +ENSG00000125637 PSD4 seminal vesicle glandular cells Medium Enhanced Q8NDX1 +ENSG00000125637 PSD4 testis cells in seminiferous ducts Medium Enhanced Q8NDX1 +ENSG00000125651 GTF2F1 epididymis glandular cells High Supported P35269 +ENSG00000125651 GTF2F1 prostate glandular cells Medium Supported P35269 +ENSG00000125651 GTF2F1 seminal vesicle glandular cells Medium Supported P35269 +ENSG00000125651 GTF2F1 testis cells in seminiferous ducts High Supported P35269 +ENSG00000125651 GTF2F1 testis Leydig cells High Supported P35269 +ENSG00000125656 CLPP epididymis glandular cells Medium Supported Q16740 +ENSG00000125656 CLPP prostate glandular cells High Supported Q16740 +ENSG00000125656 CLPP seminal vesicle glandular cells High Supported Q16740 +ENSG00000125656 CLPP testis cells in seminiferous ducts High Supported Q16740 +ENSG00000125656 CLPP testis Leydig cells High Supported Q16740 +ENSG00000125676 THOC2 epididymis glandular cells High Supported Q8NI27 +ENSG00000125676 THOC2 prostate glandular cells Medium Supported Q8NI27 +ENSG00000125676 THOC2 seminal vesicle glandular cells High Supported Q8NI27 +ENSG00000125676 THOC2 testis cells in seminiferous ducts High Supported Q8NI27 +ENSG00000125676 THOC2 testis Leydig cells High Supported Q8NI27 +ENSG00000125743 SNRPD2 epididymis glandular cells High Supported P62316 +ENSG00000125743 SNRPD2 prostate glandular cells High Supported P62316 +ENSG00000125743 SNRPD2 seminal vesicle glandular cells Medium Supported P62316 +ENSG00000125743 SNRPD2 testis cells in seminiferous ducts High Supported P62316 +ENSG00000125743 SNRPD2 testis Leydig cells High Supported P62316 +ENSG00000125753 VASP epididymis glandular cells Medium Enhanced P50552 +ENSG00000125753 VASP prostate glandular cells High Enhanced P50552 +ENSG00000125753 VASP seminal vesicle glandular cells Medium Enhanced P50552 +ENSG00000125753 VASP testis cells in seminiferous ducts High Enhanced P50552 +ENSG00000125753 VASP testis Leydig cells Low Enhanced P50552 +ENSG00000125775 SDCBP2 prostate glandular cells Medium Enhanced Q9H190 +ENSG00000125775 SDCBP2 testis cells in seminiferous ducts High Enhanced Q9H190 +ENSG00000125798 FOXA2 prostate glandular cells Low Enhanced Q9Y261 +ENSG00000125827 TMX4 epididymis glandular cells Medium Enhanced Q9H1E5 +ENSG00000125827 TMX4 prostate glandular cells Medium Enhanced Q9H1E5 +ENSG00000125827 TMX4 seminal vesicle glandular cells Medium Enhanced Q9H1E5 +ENSG00000125827 TMX4 testis cells in seminiferous ducts High Enhanced Q9H1E5 +ENSG00000125827 TMX4 testis Leydig cells Medium Enhanced Q9H1E5 +ENSG00000125831 CST11 epididymis glandular cells High Enhanced Q9H112 +ENSG00000125844 RRBP1 epididymis glandular cells High Enhanced Q9P2E9 +ENSG00000125844 RRBP1 prostate glandular cells High Enhanced Q9P2E9 +ENSG00000125844 RRBP1 seminal vesicle glandular cells High Enhanced Q9P2E9 +ENSG00000125844 RRBP1 testis cells in seminiferous ducts High Enhanced Q9P2E9 +ENSG00000125844 RRBP1 testis Leydig cells High Enhanced Q9P2E9 +ENSG00000125846 ZNF133 epididymis glandular cells Medium Enhanced P52736 +ENSG00000125846 ZNF133 prostate glandular cells Low Enhanced P52736 +ENSG00000125846 ZNF133 seminal vesicle glandular cells Low Enhanced P52736 +ENSG00000125846 ZNF133 testis cells in seminiferous ducts Medium Enhanced P52736 +ENSG00000125846 ZNF133 testis Leydig cells Medium Enhanced P52736 +ENSG00000125848 FLRT3 epididymis glandular cells Medium Enhanced Q9NZU0 +ENSG00000125848 FLRT3 prostate glandular cells Low Enhanced Q9NZU0 +ENSG00000125848 FLRT3 seminal vesicle glandular cells Low Enhanced Q9NZU0 +ENSG00000125848 FLRT3 testis cells in seminiferous ducts Low Enhanced Q9NZU0 +ENSG00000125848 FLRT3 testis Leydig cells Low Enhanced Q9NZU0 +ENSG00000125863 MKKS epididymis glandular cells Medium Enhanced Q9NPJ1 +ENSG00000125863 MKKS prostate glandular cells Medium Enhanced Q9NPJ1 +ENSG00000125863 MKKS seminal vesicle glandular cells Medium Enhanced Q9NPJ1 +ENSG00000125863 MKKS testis cells in seminiferous ducts High Enhanced Q9NPJ1 +ENSG00000125863 MKKS testis Leydig cells High Enhanced Q9NPJ1 +ENSG00000125870 SNRPB2 epididymis glandular cells High Supported P08579 +ENSG00000125870 SNRPB2 prostate glandular cells Medium Supported P08579 +ENSG00000125870 SNRPB2 seminal vesicle glandular cells Medium Supported P08579 +ENSG00000125870 SNRPB2 testis cells in seminiferous ducts High Supported P08579 +ENSG00000125870 SNRPB2 testis Leydig cells Medium Supported P08579 +ENSG00000125900 SIRPD testis elongated or late spermatids High Enhanced Q9H106 +ENSG00000125900 SIRPD testis Leydig cells Low Enhanced Q9H106 +ENSG00000125900 SIRPD testis pachytene spermatocytes Medium Enhanced Q9H106 +ENSG00000125900 SIRPD testis peritubular cells High Enhanced Q9H106 +ENSG00000125900 SIRPD testis round or early spermatids High Enhanced Q9H106 +ENSG00000125901 MRPS26 epididymis glandular cells High Supported Q9BYN8 +ENSG00000125901 MRPS26 prostate glandular cells High Supported Q9BYN8 +ENSG00000125901 MRPS26 seminal vesicle glandular cells High Supported Q9BYN8 +ENSG00000125901 MRPS26 testis cells in seminiferous ducts Medium Supported Q9BYN8 +ENSG00000125901 MRPS26 testis Leydig cells High Supported Q9BYN8 +ENSG00000125903 DEFB129 epididymis glandular cells High Supported Q9H1M3 +ENSG00000125931 CITED1 epididymis glandular cells Medium Enhanced Q99966 +ENSG00000125931 CITED1 testis cells in seminiferous ducts Low Enhanced Q99966 +ENSG00000125931 CITED1 testis Leydig cells Low Enhanced Q99966 +ENSG00000125944 HNRNPR epididymis glandular cells Medium Enhanced NA +ENSG00000125944 HNRNPR prostate glandular cells Medium Enhanced NA +ENSG00000125944 HNRNPR seminal vesicle glandular cells Medium Enhanced NA +ENSG00000125944 HNRNPR testis cells in seminiferous ducts High Enhanced NA +ENSG00000125944 HNRNPR testis Leydig cells Medium Enhanced NA +ENSG00000125945 ZNF436 epididymis glandular cells Medium Enhanced NA +ENSG00000125945 ZNF436 prostate glandular cells High Enhanced NA +ENSG00000125945 ZNF436 seminal vesicle glandular cells Medium Enhanced NA +ENSG00000125945 ZNF436 testis cells in seminiferous ducts High Enhanced NA +ENSG00000125945 ZNF436 testis Leydig cells Low Enhanced NA +ENSG00000125952 MAX epididymis glandular cells High Enhanced P61244 +ENSG00000125952 MAX prostate glandular cells High Enhanced P61244 +ENSG00000125952 MAX seminal vesicle glandular cells High Enhanced P61244 +ENSG00000125952 MAX testis cells in seminiferous ducts Medium Enhanced P61244 +ENSG00000125952 MAX testis Leydig cells Low Enhanced P61244 +ENSG00000125967 NECAB3 epididymis glandular cells Medium Supported Q96P71 +ENSG00000125967 NECAB3 prostate glandular cells Low Supported Q96P71 +ENSG00000125967 NECAB3 seminal vesicle glandular cells High Supported Q96P71 +ENSG00000125967 NECAB3 testis cells in seminiferous ducts High Supported Q96P71 +ENSG00000125967 NECAB3 testis Leydig cells High Supported Q96P71 +ENSG00000125970 RALY epididymis glandular cells High Enhanced Q9UKM9 +ENSG00000125970 RALY prostate glandular cells High Enhanced Q9UKM9 +ENSG00000125970 RALY seminal vesicle glandular cells Medium Enhanced Q9UKM9 +ENSG00000125970 RALY testis cells in seminiferous ducts High Enhanced Q9UKM9 +ENSG00000125970 RALY testis Leydig cells Medium Enhanced Q9UKM9 +ENSG00000125999 BPIFB1 testis Leydig cells Low Supported Q8TDL5 +ENSG00000126016 AMOT epididymis glandular cells Low Enhanced Q4VCS5 +ENSG00000126016 AMOT testis cells in seminiferous ducts Low Enhanced Q4VCS5 +ENSG00000126016 AMOT testis Leydig cells Low Enhanced Q4VCS5 +ENSG00000126062 TMEM115 epididymis glandular cells Medium Supported Q12893 +ENSG00000126062 TMEM115 prostate glandular cells Medium Supported Q12893 +ENSG00000126062 TMEM115 seminal vesicle glandular cells Medium Supported Q12893 +ENSG00000126062 TMEM115 testis cells in seminiferous ducts Medium Supported Q12893 +ENSG00000126062 TMEM115 testis Leydig cells High Supported Q12893 +ENSG00000126231 PROZ epididymis glandular cells Low Enhanced P22891 +ENSG00000126231 PROZ seminal vesicle glandular cells Low Enhanced P22891 +ENSG00000126231 PROZ testis Leydig cells Low Enhanced P22891 +ENSG00000126254 RBM42 epididymis glandular cells High Supported Q9BTD8 +ENSG00000126254 RBM42 prostate glandular cells Medium Supported Q9BTD8 +ENSG00000126254 RBM42 seminal vesicle glandular cells High Supported Q9BTD8 +ENSG00000126254 RBM42 testis cells in seminiferous ducts High Supported Q9BTD8 +ENSG00000126254 RBM42 testis Leydig cells Medium Supported Q9BTD8 +ENSG00000126261 UBA2 epididymis glandular cells High Supported Q9UBT2 +ENSG00000126261 UBA2 prostate glandular cells High Supported Q9UBT2 +ENSG00000126261 UBA2 seminal vesicle glandular cells High Supported Q9UBT2 +ENSG00000126261 UBA2 testis cells in seminiferous ducts High Supported Q9UBT2 +ENSG00000126261 UBA2 testis Leydig cells High Supported Q9UBT2 +ENSG00000126267 COX6B1 epididymis glandular cells High Enhanced P14854 +ENSG00000126267 COX6B1 prostate glandular cells High Enhanced P14854 +ENSG00000126267 COX6B1 seminal vesicle glandular cells High Enhanced P14854 +ENSG00000126267 COX6B1 testis cells in seminiferous ducts Medium Enhanced P14854 +ENSG00000126267 COX6B1 testis Leydig cells Low Enhanced P14854 +ENSG00000126432 PRDX5 epididymis glandular cells Medium Enhanced P30044 +ENSG00000126432 PRDX5 prostate glandular cells Medium Enhanced P30044 +ENSG00000126432 PRDX5 seminal vesicle glandular cells Medium Enhanced P30044 +ENSG00000126432 PRDX5 testis cells in seminiferous ducts Medium Enhanced P30044 +ENSG00000126432 PRDX5 testis Leydig cells High Enhanced P30044 +ENSG00000126457 PRMT1 epididymis glandular cells Medium Enhanced Q99873 +ENSG00000126457 PRMT1 prostate glandular cells Medium Enhanced Q99873 +ENSG00000126457 PRMT1 testis cells in seminiferous ducts Medium Enhanced Q99873 +ENSG00000126457 PRMT1 testis Leydig cells Medium Enhanced Q99873 +ENSG00000126467 TSKS testis cells in seminiferous ducts High Enhanced Q9UJT2 +ENSG00000126581 BECN1 epididymis glandular cells Medium Enhanced Q14457 +ENSG00000126581 BECN1 prostate glandular cells Low Enhanced Q14457 +ENSG00000126581 BECN1 seminal vesicle glandular cells Low Enhanced Q14457 +ENSG00000126581 BECN1 testis cells in seminiferous ducts Medium Enhanced Q14457 +ENSG00000126581 BECN1 testis Leydig cells Medium Enhanced Q14457 +ENSG00000126602 TRAP1 epididymis glandular cells High Enhanced Q12931 +ENSG00000126602 TRAP1 prostate glandular cells High Enhanced Q12931 +ENSG00000126602 TRAP1 seminal vesicle glandular cells High Enhanced Q12931 +ENSG00000126602 TRAP1 testis cells in seminiferous ducts High Enhanced Q12931 +ENSG00000126602 TRAP1 testis Leydig cells High Enhanced Q12931 +ENSG00000126653 NSRP1 epididymis glandular cells High Enhanced Q9H0G5 +ENSG00000126653 NSRP1 prostate glandular cells Low Enhanced Q9H0G5 +ENSG00000126653 NSRP1 seminal vesicle glandular cells High Enhanced Q9H0G5 +ENSG00000126653 NSRP1 testis cells in seminiferous ducts High Enhanced Q9H0G5 +ENSG00000126653 NSRP1 testis Leydig cells Medium Enhanced Q9H0G5 +ENSG00000126746 ZNF384 epididymis glandular cells Medium Supported Q8TF68 +ENSG00000126746 ZNF384 prostate glandular cells High Supported Q8TF68 +ENSG00000126746 ZNF384 seminal vesicle glandular cells Medium Supported Q8TF68 +ENSG00000126746 ZNF384 testis cells in seminiferous ducts Medium Supported Q8TF68 +ENSG00000126746 ZNF384 testis Leydig cells Medium Supported Q8TF68 +ENSG00000126749 EMG1 seminal vesicle glandular cells Low Supported Q92979 +ENSG00000126749 EMG1 testis cells in seminiferous ducts Low Supported Q92979 +ENSG00000126749 EMG1 testis Leydig cells Low Supported Q92979 +ENSG00000126752 SSX1 testis pachytene spermatocytes Low Supported Q16384 +ENSG00000126752 SSX1 testis preleptotene spermatocytes Medium Supported Q16384 +ENSG00000126752 SSX1 testis spermatogonia High Supported Q16384 +ENSG00000126767 ELK1 epididymis glandular cells Medium Enhanced P19419 +ENSG00000126767 ELK1 prostate glandular cells Low Enhanced P19419 +ENSG00000126767 ELK1 seminal vesicle glandular cells Medium Enhanced P19419 +ENSG00000126767 ELK1 testis cells in seminiferous ducts Medium Enhanced P19419 +ENSG00000126767 ELK1 testis Leydig cells High Enhanced P19419 +ENSG00000126777 KTN1 epididymis glandular cells High Enhanced Q86UP2 +ENSG00000126777 KTN1 prostate glandular cells High Enhanced Q86UP2 +ENSG00000126777 KTN1 seminal vesicle glandular cells High Enhanced Q86UP2 +ENSG00000126777 KTN1 testis cells in seminiferous ducts High Enhanced Q86UP2 +ENSG00000126777 KTN1 testis Leydig cells Medium Enhanced Q86UP2 +ENSG00000126778 SIX1 prostate glandular cells Medium Enhanced Q15475 +ENSG00000126778 SIX1 testis cells in seminiferous ducts Low Enhanced Q15475 +ENSG00000126787 DLGAP5 epididymis glandular cells Low Enhanced Q15398 +ENSG00000126787 DLGAP5 testis elongated or late spermatids Medium Enhanced Q15398 +ENSG00000126787 DLGAP5 testis pachytene spermatocytes High Enhanced Q15398 +ENSG00000126787 DLGAP5 testis preleptotene spermatocytes High Enhanced Q15398 +ENSG00000126787 DLGAP5 testis round or early spermatids High Enhanced Q15398 +ENSG00000126787 DLGAP5 testis spermatogonia High Enhanced Q15398 +ENSG00000126803 HSPA2 testis elongated or late spermatids High Enhanced P54652 +ENSG00000126803 HSPA2 testis pachytene spermatocytes High Enhanced P54652 +ENSG00000126803 HSPA2 testis preleptotene spermatocytes Low Enhanced P54652 +ENSG00000126803 HSPA2 testis round or early spermatids High Enhanced P54652 +ENSG00000126803 HSPA2 testis spermatogonia Low Enhanced P54652 +ENSG00000126814 TRMT5 epididymis glandular cells High Supported Q32P41 +ENSG00000126814 TRMT5 prostate glandular cells High Supported Q32P41 +ENSG00000126814 TRMT5 seminal vesicle glandular cells High Supported Q32P41 +ENSG00000126814 TRMT5 testis cells in seminiferous ducts High Supported Q32P41 +ENSG00000126814 TRMT5 testis Leydig cells High Supported Q32P41 +ENSG00000126822 PLEKHG3 epididymis glandular cells High Enhanced A1L390 +ENSG00000126822 PLEKHG3 seminal vesicle glandular cells Medium Enhanced A1L390 +ENSG00000126822 PLEKHG3 testis cells in seminiferous ducts Medium Enhanced A1L390 +ENSG00000126822 PLEKHG3 testis Leydig cells Medium Enhanced A1L390 +ENSG00000126838 PZP prostate glandular cells Low Supported P20742 +ENSG00000126838 PZP testis cells in seminiferous ducts Medium Supported P20742 +ENSG00000126838 PZP testis Leydig cells High Supported P20742 +ENSG00000126858 RHOT1 epididymis glandular cells High Enhanced Q8IXI2 +ENSG00000126858 RHOT1 prostate glandular cells High Enhanced Q8IXI2 +ENSG00000126858 RHOT1 seminal vesicle glandular cells High Enhanced Q8IXI2 +ENSG00000126858 RHOT1 testis cells in seminiferous ducts High Enhanced Q8IXI2 +ENSG00000126858 RHOT1 testis Leydig cells High Enhanced Q8IXI2 +ENSG00000126878 AIF1L epididymis glandular cells Medium Enhanced Q9BQI0 +ENSG00000126878 AIF1L seminal vesicle glandular cells Medium Enhanced Q9BQI0 +ENSG00000126890 CTAG2 testis elongated or late spermatids Medium Enhanced O75638 +ENSG00000126890 CTAG2 testis Leydig cells Low Enhanced O75638 +ENSG00000126890 CTAG2 testis pachytene spermatocytes Medium Enhanced O75638 +ENSG00000126890 CTAG2 testis preleptotene spermatocytes High Enhanced O75638 +ENSG00000126890 CTAG2 testis round or early spermatids Medium Enhanced O75638 +ENSG00000126890 CTAG2 testis spermatogonia High Enhanced O75638 +ENSG00000126934 MAP2K2 epididymis glandular cells High Supported P36507 +ENSG00000126934 MAP2K2 prostate glandular cells High Supported P36507 +ENSG00000126934 MAP2K2 seminal vesicle glandular cells High Supported P36507 +ENSG00000126934 MAP2K2 testis cells in seminiferous ducts Medium Supported P36507 +ENSG00000126934 MAP2K2 testis Leydig cells Medium Supported P36507 +ENSG00000126945 HNRNPH2 epididymis glandular cells High Supported P55795 +ENSG00000126945 HNRNPH2 prostate glandular cells High Supported P55795 +ENSG00000126945 HNRNPH2 seminal vesicle glandular cells High Supported P55795 +ENSG00000126945 HNRNPH2 testis cells in seminiferous ducts High Supported P55795 +ENSG00000126945 HNRNPH2 testis Leydig cells High Supported P55795 +ENSG00000126947 ARMCX1 epididymis glandular cells Low Supported Q9P291 +ENSG00000126947 ARMCX1 prostate glandular cells Low Supported Q9P291 +ENSG00000126947 ARMCX1 seminal vesicle glandular cells Medium Supported Q9P291 +ENSG00000126947 ARMCX1 testis cells in seminiferous ducts Low Supported Q9P291 +ENSG00000126947 ARMCX1 testis Leydig cells Low Supported Q9P291 +ENSG00000126953 TIMM8A epididymis glandular cells Low Supported O60220 +ENSG00000126953 TIMM8A prostate glandular cells Medium Supported O60220 +ENSG00000126953 TIMM8A seminal vesicle glandular cells Medium Supported O60220 +ENSG00000126953 TIMM8A testis Leydig cells Low Supported O60220 +ENSG00000127022 CANX epididymis glandular cells High Enhanced D6RB85 +ENSG00000127022 CANX prostate glandular cells High Enhanced D6RB85 +ENSG00000127022 CANX seminal vesicle glandular cells High Enhanced D6RB85 +ENSG00000127022 CANX testis cells in seminiferous ducts High Enhanced D6RB85 +ENSG00000127022 CANX testis Leydig cells High Enhanced D6RB85 +ENSG00000127152 BCL11B testis cells in seminiferous ducts Medium Enhanced Q9C0K0 +ENSG00000127324 TSPAN8 prostate glandular cells Medium Enhanced P19075 +ENSG00000127324 TSPAN8 testis Leydig cells Low Enhanced P19075 +ENSG00000127415 IDUA epididymis glandular cells High Enhanced P35475 +ENSG00000127415 IDUA prostate glandular cells Medium Enhanced P35475 +ENSG00000127415 IDUA seminal vesicle glandular cells Medium Enhanced P35475 +ENSG00000127415 IDUA testis cells in seminiferous ducts Low Enhanced P35475 +ENSG00000127415 IDUA testis Leydig cells Medium Enhanced P35475 +ENSG00000127483 HP1BP3 epididymis glandular cells Medium Supported Q5SSJ5 +ENSG00000127483 HP1BP3 prostate glandular cells Medium Supported Q5SSJ5 +ENSG00000127483 HP1BP3 seminal vesicle glandular cells Medium Supported Q5SSJ5 +ENSG00000127483 HP1BP3 testis cells in seminiferous ducts Low Supported Q5SSJ5 +ENSG00000127483 HP1BP3 testis Leydig cells Medium Supported Q5SSJ5 +ENSG00000127616 SMARCA4 epididymis glandular cells High Supported P51532 +ENSG00000127616 SMARCA4 prostate glandular cells High Supported P51532 +ENSG00000127616 SMARCA4 seminal vesicle glandular cells Medium Supported P51532 +ENSG00000127616 SMARCA4 testis cells in seminiferous ducts High Supported P51532 +ENSG00000127616 SMARCA4 testis Leydig cells Medium Supported P51532 +ENSG00000127884 ECHS1 epididymis glandular cells High Enhanced P30084 +ENSG00000127884 ECHS1 prostate glandular cells High Enhanced P30084 +ENSG00000127884 ECHS1 seminal vesicle glandular cells High Enhanced P30084 +ENSG00000127884 ECHS1 testis cells in seminiferous ducts High Enhanced P30084 +ENSG00000127884 ECHS1 testis Leydig cells High Enhanced P30084 +ENSG00000127914 AKAP9 epididymis glandular cells High Enhanced Q99996 +ENSG00000127914 AKAP9 prostate glandular cells Medium Enhanced Q99996 +ENSG00000127914 AKAP9 seminal vesicle glandular cells Medium Enhanced Q99996 +ENSG00000127914 AKAP9 testis cells in seminiferous ducts Medium Enhanced Q99996 +ENSG00000127914 AKAP9 testis Leydig cells Medium Enhanced Q99996 +ENSG00000127946 HIP1 epididymis glandular cells High Enhanced O00291 +ENSG00000127946 HIP1 prostate glandular cells Medium Enhanced O00291 +ENSG00000127946 HIP1 seminal vesicle glandular cells Medium Enhanced O00291 +ENSG00000127946 HIP1 testis cells in seminiferous ducts Medium Enhanced O00291 +ENSG00000127946 HIP1 testis Leydig cells Medium Enhanced O00291 +ENSG00000127948 POR epididymis glandular cells High Enhanced P16435 +ENSG00000127948 POR prostate glandular cells Medium Enhanced P16435 +ENSG00000127948 POR seminal vesicle glandular cells High Enhanced P16435 +ENSG00000127948 POR testis cells in seminiferous ducts High Enhanced P16435 +ENSG00000127948 POR testis Leydig cells High Enhanced P16435 +ENSG00000128040 SPINK2 epididymis glandular cells High Enhanced P20155 +ENSG00000128040 SPINK2 seminal vesicle glandular cells High Enhanced P20155 +ENSG00000128040 SPINK2 testis cells in seminiferous ducts High Enhanced P20155 +ENSG00000128266 GNAZ epididymis glandular cells Low Enhanced P19086 +ENSG00000128266 GNAZ seminal vesicle glandular cells Low Enhanced P19086 +ENSG00000128266 GNAZ testis Leydig cells Low Enhanced P19086 +ENSG00000128309 MPST epididymis glandular cells Medium Enhanced P25325 +ENSG00000128309 MPST prostate glandular cells Medium Enhanced P25325 +ENSG00000128309 MPST seminal vesicle glandular cells Medium Enhanced P25325 +ENSG00000128309 MPST testis cells in seminiferous ducts Low Enhanced P25325 +ENSG00000128309 MPST testis Leydig cells Medium Enhanced P25325 +ENSG00000128311 TST epididymis glandular cells Low Enhanced Q16762 +ENSG00000128311 TST prostate glandular cells Medium Enhanced Q16762 +ENSG00000128311 TST seminal vesicle glandular cells Low Enhanced Q16762 +ENSG00000128311 TST testis cells in seminiferous ducts Medium Enhanced Q16762 +ENSG00000128311 TST testis Leydig cells High Enhanced Q16762 +ENSG00000128322 IGLL1 testis elongated or late spermatids High Enhanced P15814 +ENSG00000128322 IGLL1 testis pachytene spermatocytes Medium Enhanced P15814 +ENSG00000128322 IGLL1 testis round or early spermatids Medium Enhanced P15814 +ENSG00000128422 KRT17 epididymis glandular cells Medium Enhanced Q04695 +ENSG00000128422 KRT17 prostate glandular cells High Enhanced Q04695 +ENSG00000128422 KRT17 seminal vesicle glandular cells Medium Enhanced Q04695 +ENSG00000128422 KRT17 testis Leydig cells Medium Enhanced Q04695 +ENSG00000128487 SPECC1 epididymis glandular cells High Enhanced Q5M775 +ENSG00000128487 SPECC1 prostate glandular cells Medium Enhanced Q5M775 +ENSG00000128487 SPECC1 testis cells in seminiferous ducts Medium Enhanced Q5M775 +ENSG00000128487 SPECC1 testis Leydig cells Medium Enhanced Q5M775 +ENSG00000128524 ATP6V1F epididymis glandular cells Medium Enhanced Q16864 +ENSG00000128524 ATP6V1F prostate glandular cells Medium Enhanced Q16864 +ENSG00000128524 ATP6V1F seminal vesicle glandular cells Low Enhanced Q16864 +ENSG00000128524 ATP6V1F testis cells in seminiferous ducts Medium Enhanced Q16864 +ENSG00000128524 ATP6V1F testis Leydig cells Medium Enhanced Q16864 +ENSG00000128567 PODXL seminal vesicle glandular cells Low Enhanced O00592 +ENSG00000128573 FOXP2 seminal vesicle glandular cells Low Enhanced O15409 +ENSG00000128590 DNAJB9 epididymis glandular cells Medium Supported Q9UBS3 +ENSG00000128590 DNAJB9 prostate glandular cells Low Supported Q9UBS3 +ENSG00000128590 DNAJB9 seminal vesicle glandular cells Low Supported Q9UBS3 +ENSG00000128590 DNAJB9 testis cells in seminiferous ducts Medium Supported Q9UBS3 +ENSG00000128590 DNAJB9 testis Leydig cells Medium Supported Q9UBS3 +ENSG00000128595 CALU epididymis glandular cells Medium Supported O43852 +ENSG00000128595 CALU prostate glandular cells Medium Supported O43852 +ENSG00000128595 CALU seminal vesicle glandular cells High Supported O43852 +ENSG00000128595 CALU testis cells in seminiferous ducts Medium Supported O43852 +ENSG00000128595 CALU testis Leydig cells Medium Supported O43852 +ENSG00000128596 CCDC136 testis cells in seminiferous ducts High Enhanced Q96JN2 +ENSG00000128604 IRF5 testis cells in seminiferous ducts Low Enhanced Q13568 +ENSG00000128609 NDUFA5 epididymis glandular cells Medium Supported Q16718 +ENSG00000128609 NDUFA5 prostate glandular cells Medium Supported Q16718 +ENSG00000128609 NDUFA5 seminal vesicle glandular cells High Supported Q16718 +ENSG00000128609 NDUFA5 testis cells in seminiferous ducts Medium Supported Q16718 +ENSG00000128609 NDUFA5 testis Leydig cells High Supported Q16718 +ENSG00000128683 GAD1 prostate glandular cells Low Enhanced Q99259 +ENSG00000128708 HAT1 epididymis glandular cells High Enhanced O14929 +ENSG00000128708 HAT1 prostate glandular cells Medium Enhanced O14929 +ENSG00000128708 HAT1 seminal vesicle glandular cells Medium Enhanced O14929 +ENSG00000128708 HAT1 testis cells in seminiferous ducts High Enhanced O14929 +ENSG00000128708 HAT1 testis Leydig cells Medium Enhanced O14929 +ENSG00000128833 MYO5C epididymis glandular cells Medium Enhanced Q9NQX4 +ENSG00000128833 MYO5C prostate glandular cells Medium Enhanced Q9NQX4 +ENSG00000128833 MYO5C seminal vesicle glandular cells Medium Enhanced Q9NQX4 +ENSG00000128833 MYO5C testis cells in seminiferous ducts Medium Enhanced Q9NQX4 +ENSG00000128849 CGNL1 prostate glandular cells Medium Enhanced Q0VF96 +ENSG00000128849 CGNL1 seminal vesicle glandular cells Medium Enhanced Q0VF96 +ENSG00000128928 IVD epididymis glandular cells High Enhanced P26440 +ENSG00000128928 IVD prostate glandular cells High Enhanced P26440 +ENSG00000128928 IVD seminal vesicle glandular cells High Enhanced P26440 +ENSG00000128928 IVD testis cells in seminiferous ducts High Enhanced P26440 +ENSG00000128928 IVD testis Leydig cells High Enhanced P26440 +ENSG00000128944 KNSTRN epididymis glandular cells Medium Enhanced Q9Y448 +ENSG00000128944 KNSTRN testis cells in seminiferous ducts High Enhanced Q9Y448 +ENSG00000128944 KNSTRN testis Leydig cells Low Enhanced Q9Y448 +ENSG00000128951 DUT epididymis glandular cells Low Enhanced P33316 +ENSG00000128951 DUT prostate glandular cells Medium Enhanced P33316 +ENSG00000128951 DUT seminal vesicle glandular cells Medium Enhanced P33316 +ENSG00000128951 DUT testis cells in seminiferous ducts Medium Enhanced P33316 +ENSG00000128951 DUT testis Leydig cells Medium Enhanced P33316 +ENSG00000129071 MBD4 epididymis glandular cells Low Supported O95243 +ENSG00000129071 MBD4 prostate glandular cells Medium Supported O95243 +ENSG00000129071 MBD4 seminal vesicle glandular cells Low Supported O95243 +ENSG00000129071 MBD4 testis cells in seminiferous ducts Medium Supported O95243 +ENSG00000129071 MBD4 testis Leydig cells Medium Supported O95243 +ENSG00000129083 COPB1 epididymis glandular cells High Supported P53618 +ENSG00000129083 COPB1 prostate glandular cells Medium Supported P53618 +ENSG00000129083 COPB1 seminal vesicle glandular cells High Supported P53618 +ENSG00000129083 COPB1 testis cells in seminiferous ducts High Supported P53618 +ENSG00000129083 COPB1 testis Leydig cells Medium Supported P53618 +ENSG00000129084 PSMA1 epididymis glandular cells Medium Supported P25786 +ENSG00000129084 PSMA1 prostate glandular cells Medium Supported P25786 +ENSG00000129084 PSMA1 seminal vesicle glandular cells Medium Supported P25786 +ENSG00000129084 PSMA1 testis cells in seminiferous ducts High Supported P25786 +ENSG00000129084 PSMA1 testis Leydig cells High Supported P25786 +ENSG00000129103 SUMF2 epididymis glandular cells Medium Enhanced Q8NBJ7 +ENSG00000129103 SUMF2 prostate glandular cells Low Enhanced Q8NBJ7 +ENSG00000129103 SUMF2 seminal vesicle glandular cells High Enhanced Q8NBJ7 +ENSG00000129103 SUMF2 testis cells in seminiferous ducts Low Enhanced Q8NBJ7 +ENSG00000129103 SUMF2 testis Leydig cells Medium Enhanced Q8NBJ7 +ENSG00000129116 PALLD prostate glandular cells Low Enhanced Q8WX93 +ENSG00000129116 PALLD testis Leydig cells Low Enhanced Q8WX93 +ENSG00000129158 SERGEF epididymis glandular cells Medium Supported Q9UGK8 +ENSG00000129158 SERGEF prostate glandular cells Medium Supported Q9UGK8 +ENSG00000129158 SERGEF seminal vesicle glandular cells Medium Supported Q9UGK8 +ENSG00000129158 SERGEF testis cells in seminiferous ducts High Supported Q9UGK8 +ENSG00000129158 SERGEF testis Leydig cells Medium Supported Q9UGK8 +ENSG00000129167 TPH1 epididymis glandular cells Low Enhanced P17752 +ENSG00000129167 TPH1 prostate glandular cells Medium Enhanced P17752 +ENSG00000129167 TPH1 seminal vesicle glandular cells Medium Enhanced P17752 +ENSG00000129167 TPH1 testis cells in seminiferous ducts Medium Enhanced P17752 +ENSG00000129167 TPH1 testis Leydig cells Medium Enhanced P17752 +ENSG00000129194 SOX15 testis cells in seminiferous ducts Low Enhanced O60248 +ENSG00000129194 SOX15 testis Leydig cells Low Enhanced O60248 +ENSG00000129245 FXR2 epididymis glandular cells Medium Supported P51116 +ENSG00000129245 FXR2 prostate glandular cells Medium Supported P51116 +ENSG00000129245 FXR2 seminal vesicle glandular cells Medium Supported P51116 +ENSG00000129245 FXR2 testis cells in seminiferous ducts High Supported P51116 +ENSG00000129245 FXR2 testis Leydig cells Medium Supported P51116 +ENSG00000129315 CCNT1 epididymis glandular cells Medium Supported O60563 +ENSG00000129315 CCNT1 prostate glandular cells Medium Supported O60563 +ENSG00000129315 CCNT1 testis cells in seminiferous ducts Medium Supported O60563 +ENSG00000129315 CCNT1 testis Leydig cells Medium Supported O60563 +ENSG00000129351 ILF3 epididymis glandular cells High Supported Q12906 +ENSG00000129351 ILF3 prostate glandular cells High Supported Q12906 +ENSG00000129351 ILF3 seminal vesicle glandular cells High Supported Q12906 +ENSG00000129351 ILF3 testis cells in seminiferous ducts High Supported Q12906 +ENSG00000129351 ILF3 testis Leydig cells High Supported Q12906 +ENSG00000129355 CDKN2D testis cells in seminiferous ducts High Enhanced P55273 +ENSG00000129514 FOXA1 prostate glandular cells High Enhanced P55317 +ENSG00000129538 RNASE1 epididymis glandular cells High Supported P07998 +ENSG00000129538 RNASE1 seminal vesicle glandular cells Medium Supported P07998 +ENSG00000129538 RNASE1 testis cells in seminiferous ducts Low Supported P07998 +ENSG00000129646 QRICH2 testis cells in seminiferous ducts High Enhanced Q9H0J4 +ENSG00000129654 FOXJ1 testis Leydig cells Low Enhanced Q92949 +ENSG00000129810 SGO1 testis pachytene spermatocytes Medium Enhanced Q5FBB7 +ENSG00000129810 SGO1 testis spermatogonia Low Enhanced Q5FBB7 +ENSG00000129862 VCY1B testis elongated or late spermatids Medium Supported NA +ENSG00000129862 VCY1B testis pachytene spermatocytes High Supported NA +ENSG00000129862 VCY1B testis preleptotene spermatocytes High Supported NA +ENSG00000129862 VCY1B testis round or early spermatids High Supported NA +ENSG00000129862 VCY1B testis spermatogonia High Supported NA +ENSG00000129864 VCY testis elongated or late spermatids Medium Supported NA +ENSG00000129864 VCY testis pachytene spermatocytes High Supported NA +ENSG00000129864 VCY testis preleptotene spermatocytes High Supported NA +ENSG00000129864 VCY testis round or early spermatids High Supported NA +ENSG00000129864 VCY testis spermatogonia High Supported NA +ENSG00000130024 PHF10 epididymis glandular cells High Supported Q8WUB8 +ENSG00000130024 PHF10 prostate glandular cells High Supported Q8WUB8 +ENSG00000130024 PHF10 seminal vesicle glandular cells Medium Supported Q8WUB8 +ENSG00000130024 PHF10 testis cells in seminiferous ducts High Supported Q8WUB8 +ENSG00000130024 PHF10 testis Leydig cells High Supported Q8WUB8 +ENSG00000130038 CRACR2A epididymis glandular cells Medium Enhanced Q9BSW2 +ENSG00000130038 CRACR2A seminal vesicle glandular cells Low Enhanced Q9BSW2 +ENSG00000130066 SAT1 epididymis glandular cells Medium Supported P21673 +ENSG00000130066 SAT1 prostate glandular cells Medium Supported P21673 +ENSG00000130066 SAT1 seminal vesicle glandular cells Low Supported P21673 +ENSG00000130066 SAT1 testis cells in seminiferous ducts Medium Supported P21673 +ENSG00000130066 SAT1 testis Leydig cells Medium Supported P21673 +ENSG00000130119 GNL3L epididymis glandular cells High Supported Q9NVN8 +ENSG00000130119 GNL3L prostate glandular cells Medium Supported Q9NVN8 +ENSG00000130119 GNL3L seminal vesicle glandular cells Medium Supported Q9NVN8 +ENSG00000130119 GNL3L testis cells in seminiferous ducts Medium Supported Q9NVN8 +ENSG00000130119 GNL3L testis Leydig cells High Supported Q9NVN8 +ENSG00000130175 PRKCSH epididymis glandular cells High Enhanced P14314 +ENSG00000130175 PRKCSH prostate glandular cells Medium Enhanced P14314 +ENSG00000130175 PRKCSH seminal vesicle glandular cells High Enhanced P14314 +ENSG00000130175 PRKCSH testis cells in seminiferous ducts High Enhanced P14314 +ENSG00000130175 PRKCSH testis Leydig cells Medium Enhanced P14314 +ENSG00000130202 NECTIN2 epididymis glandular cells Medium Enhanced Q92692 +ENSG00000130202 NECTIN2 prostate glandular cells Medium Enhanced Q92692 +ENSG00000130202 NECTIN2 seminal vesicle glandular cells Medium Enhanced Q92692 +ENSG00000130202 NECTIN2 testis cells in seminiferous ducts High Enhanced Q92692 +ENSG00000130202 NECTIN2 testis Leydig cells Medium Enhanced Q92692 +ENSG00000130203 APOE testis Leydig cells Low Enhanced P02649 +ENSG00000130204 TOMM40 epididymis glandular cells Medium Supported O96008 +ENSG00000130204 TOMM40 prostate glandular cells Medium Supported O96008 +ENSG00000130204 TOMM40 seminal vesicle glandular cells Medium Supported O96008 +ENSG00000130204 TOMM40 testis cells in seminiferous ducts Medium Supported O96008 +ENSG00000130204 TOMM40 testis Leydig cells Medium Supported O96008 +ENSG00000130234 ACE2 seminal vesicle glandular cells Low Enhanced Q9BYF1 +ENSG00000130234 ACE2 testis cells in seminiferous ducts High Enhanced Q9BYF1 +ENSG00000130234 ACE2 testis Leydig cells High Enhanced Q9BYF1 +ENSG00000130255 RPL36 epididymis glandular cells High Supported Q9Y3U8 +ENSG00000130255 RPL36 prostate glandular cells High Supported Q9Y3U8 +ENSG00000130255 RPL36 seminal vesicle glandular cells High Supported Q9Y3U8 +ENSG00000130255 RPL36 testis cells in seminiferous ducts Medium Supported Q9Y3U8 +ENSG00000130255 RPL36 testis Leydig cells High Supported Q9Y3U8 +ENSG00000130377 ACSBG2 testis elongated or late spermatids High Enhanced Q5FVE4 +ENSG00000130402 ACTN4 epididymis glandular cells Medium Supported K7EP19 +ENSG00000130402 ACTN4 prostate glandular cells Low Supported K7EP19 +ENSG00000130402 ACTN4 seminal vesicle glandular cells Medium Supported K7EP19 +ENSG00000130402 ACTN4 testis cells in seminiferous ducts Low Supported K7EP19 +ENSG00000130402 ACTN4 testis Leydig cells Medium Supported K7EP19 +ENSG00000130513 GDF15 prostate glandular cells Medium Enhanced Q99988 +ENSG00000130518 KIAA1683 testis elongated or late spermatids High Enhanced Q9H0B3 +ENSG00000130518 KIAA1683 testis round or early spermatids Low Enhanced Q9H0B3 +ENSG00000130518 KIAA1683 testis sertoli cells Low Enhanced Q9H0B3 +ENSG00000130522 JUND epididymis glandular cells High Supported P17535 +ENSG00000130522 JUND prostate glandular cells Medium Supported P17535 +ENSG00000130522 JUND seminal vesicle glandular cells Medium Supported P17535 +ENSG00000130522 JUND testis cells in seminiferous ducts Low Supported P17535 +ENSG00000130522 JUND testis Leydig cells Medium Supported P17535 +ENSG00000130529 TRPM4 prostate glandular cells High Enhanced Q8TD43 +ENSG00000130529 TRPM4 testis Leydig cells Low Enhanced Q8TD43 +ENSG00000130545 CRB3 epididymis glandular cells Low Enhanced Q9BUF7 +ENSG00000130545 CRB3 seminal vesicle glandular cells Low Enhanced Q9BUF7 +ENSG00000130545 CRB3 testis cells in seminiferous ducts Low Enhanced Q9BUF7 +ENSG00000130699 TAF4 epididymis glandular cells Medium Supported O00268 +ENSG00000130699 TAF4 prostate glandular cells Medium Supported O00268 +ENSG00000130699 TAF4 seminal vesicle glandular cells Medium Supported O00268 +ENSG00000130699 TAF4 testis cells in seminiferous ducts Medium Supported O00268 +ENSG00000130699 TAF4 testis Leydig cells Medium Supported O00268 +ENSG00000130706 ADRM1 epididymis glandular cells Medium Supported Q16186 +ENSG00000130706 ADRM1 prostate glandular cells Medium Supported Q16186 +ENSG00000130706 ADRM1 testis cells in seminiferous ducts High Supported Q16186 +ENSG00000130706 ADRM1 testis Leydig cells High Supported Q16186 +ENSG00000130707 ASS1 prostate glandular cells Low Enhanced P00966 +ENSG00000130707 ASS1 seminal vesicle glandular cells Medium Enhanced P00966 +ENSG00000130707 ASS1 testis cells in seminiferous ducts Medium Enhanced P00966 +ENSG00000130724 CHMP2A epididymis glandular cells High Enhanced O43633 +ENSG00000130724 CHMP2A prostate glandular cells Medium Enhanced O43633 +ENSG00000130724 CHMP2A seminal vesicle glandular cells High Enhanced O43633 +ENSG00000130724 CHMP2A testis cells in seminiferous ducts High Enhanced O43633 +ENSG00000130724 CHMP2A testis Leydig cells High Enhanced O43633 +ENSG00000130726 TRIM28 epididymis glandular cells High Enhanced Q13263 +ENSG00000130726 TRIM28 prostate glandular cells High Enhanced Q13263 +ENSG00000130726 TRIM28 seminal vesicle glandular cells High Enhanced Q13263 +ENSG00000130726 TRIM28 testis cells in seminiferous ducts High Enhanced Q13263 +ENSG00000130726 TRIM28 testis Leydig cells High Enhanced Q13263 +ENSG00000130749 ZC3H4 epididymis glandular cells Medium Supported Q9UPT8 +ENSG00000130749 ZC3H4 prostate glandular cells Low Supported Q9UPT8 +ENSG00000130749 ZC3H4 seminal vesicle glandular cells Medium Supported Q9UPT8 +ENSG00000130749 ZC3H4 testis cells in seminiferous ducts Medium Supported Q9UPT8 +ENSG00000130749 ZC3H4 testis Leydig cells Medium Supported Q9UPT8 +ENSG00000130764 LRRC47 epididymis glandular cells High Enhanced Q8N1G4 +ENSG00000130764 LRRC47 prostate glandular cells High Enhanced Q8N1G4 +ENSG00000130764 LRRC47 seminal vesicle glandular cells High Enhanced Q8N1G4 +ENSG00000130764 LRRC47 testis cells in seminiferous ducts High Enhanced Q8N1G4 +ENSG00000130764 LRRC47 testis Leydig cells High Enhanced Q8N1G4 +ENSG00000130770 ATPIF1 epididymis glandular cells High Supported Q9UII2 +ENSG00000130770 ATPIF1 prostate glandular cells High Supported Q9UII2 +ENSG00000130770 ATPIF1 seminal vesicle glandular cells High Supported Q9UII2 +ENSG00000130770 ATPIF1 testis cells in seminiferous ducts High Supported Q9UII2 +ENSG00000130770 ATPIF1 testis Leydig cells Low Supported Q9UII2 +ENSG00000130787 HIP1R epididymis glandular cells Medium Enhanced O75146 +ENSG00000130787 HIP1R prostate glandular cells Medium Enhanced O75146 +ENSG00000130787 HIP1R seminal vesicle glandular cells High Enhanced O75146 +ENSG00000130787 HIP1R testis cells in seminiferous ducts Medium Enhanced O75146 +ENSG00000130787 HIP1R testis Leydig cells Low Enhanced O75146 +ENSG00000130816 DNMT1 testis cells in seminiferous ducts High Enhanced P26358 +ENSG00000130826 DKC1 epididymis glandular cells High Supported O60832 +ENSG00000130826 DKC1 prostate glandular cells High Supported O60832 +ENSG00000130826 DKC1 seminal vesicle glandular cells High Supported O60832 +ENSG00000130826 DKC1 testis cells in seminiferous ducts High Supported O60832 +ENSG00000130826 DKC1 testis Leydig cells Medium Supported O60832 +ENSG00000130935 NOL11 epididymis glandular cells Medium Supported Q9H8H0 +ENSG00000130935 NOL11 prostate glandular cells Medium Supported Q9H8H0 +ENSG00000130935 NOL11 seminal vesicle glandular cells Medium Supported Q9H8H0 +ENSG00000130935 NOL11 testis cells in seminiferous ducts Medium Supported Q9H8H0 +ENSG00000130935 NOL11 testis Leydig cells High Supported Q9H8H0 +ENSG00000130943 PKDREJ testis preleptotene spermatocytes High Enhanced Q9NTG1 +ENSG00000130943 PKDREJ testis spermatogonia High Enhanced Q9NTG1 +ENSG00000130948 HSD17B3 testis Leydig cells Medium Enhanced P37058 +ENSG00000130988 RGN testis Leydig cells Low Enhanced Q15493 +ENSG00000131016 AKAP12 epididymis glandular cells Low Enhanced Q02952 +ENSG00000131016 AKAP12 testis cells in seminiferous ducts High Enhanced Q02952 +ENSG00000131016 AKAP12 testis Leydig cells Medium Enhanced Q02952 +ENSG00000131051 RBM39 epididymis glandular cells Medium Supported Q14498 +ENSG00000131051 RBM39 prostate glandular cells Medium Supported Q14498 +ENSG00000131051 RBM39 seminal vesicle glandular cells Medium Supported Q14498 +ENSG00000131051 RBM39 testis cells in seminiferous ducts Medium Supported Q14498 +ENSG00000131051 RBM39 testis Leydig cells Medium Supported Q14498 +ENSG00000131059 BPIFA3 testis elongated or late spermatids High Enhanced Q9BQP9 +ENSG00000131068 DEFB118 epididymis glandular cells Medium Enhanced Q96PH6 +ENSG00000131100 ATP6V1E1 epididymis glandular cells Medium Enhanced P36543 +ENSG00000131100 ATP6V1E1 prostate glandular cells Low Enhanced P36543 +ENSG00000131100 ATP6V1E1 seminal vesicle glandular cells Medium Enhanced P36543 +ENSG00000131100 ATP6V1E1 testis cells in seminiferous ducts Low Enhanced P36543 +ENSG00000131100 ATP6V1E1 testis Leydig cells Medium Enhanced P36543 +ENSG00000131126 TEX101 testis elongated or late spermatids High Enhanced Q9BY14 +ENSG00000131126 TEX101 testis pachytene spermatocytes High Enhanced Q9BY14 +ENSG00000131126 TEX101 testis round or early spermatids High Enhanced Q9BY14 +ENSG00000131143 COX4I1 epididymis glandular cells Medium Supported P13073 +ENSG00000131143 COX4I1 prostate glandular cells Medium Supported P13073 +ENSG00000131143 COX4I1 seminal vesicle glandular cells High Supported P13073 +ENSG00000131143 COX4I1 testis cells in seminiferous ducts Medium Supported P13073 +ENSG00000131143 COX4I1 testis Leydig cells Medium Supported P13073 +ENSG00000131238 PPT1 epididymis glandular cells High Supported P50897 +ENSG00000131238 PPT1 prostate glandular cells High Supported P50897 +ENSG00000131238 PPT1 seminal vesicle glandular cells High Supported P50897 +ENSG00000131238 PPT1 testis cells in seminiferous ducts High Supported P50897 +ENSG00000131238 PPT1 testis Leydig cells High Supported P50897 +ENSG00000131389 SLC6A6 epididymis glandular cells Low Enhanced P31641 +ENSG00000131389 SLC6A6 prostate glandular cells Medium Enhanced P31641 +ENSG00000131389 SLC6A6 seminal vesicle glandular cells Low Enhanced P31641 +ENSG00000131389 SLC6A6 testis cells in seminiferous ducts Low Enhanced P31641 +ENSG00000131462 TUBG1 epididymis glandular cells Medium Enhanced P23258 +ENSG00000131462 TUBG1 prostate glandular cells Medium Enhanced P23258 +ENSG00000131462 TUBG1 seminal vesicle glandular cells Medium Enhanced P23258 +ENSG00000131462 TUBG1 testis cells in seminiferous ducts High Enhanced P23258 +ENSG00000131462 TUBG1 testis Leydig cells Medium Enhanced P23258 +ENSG00000131467 PSME3 epididymis glandular cells High Supported P61289 +ENSG00000131467 PSME3 prostate glandular cells High Supported P61289 +ENSG00000131467 PSME3 seminal vesicle glandular cells High Supported P61289 +ENSG00000131467 PSME3 testis cells in seminiferous ducts High Supported P61289 +ENSG00000131467 PSME3 testis Leydig cells High Supported P61289 +ENSG00000131470 PSMC3IP testis elongated or late spermatids High Enhanced Q9P2W1 +ENSG00000131470 PSMC3IP testis pachytene spermatocytes Medium Enhanced Q9P2W1 +ENSG00000131470 PSMC3IP testis preleptotene spermatocytes High Enhanced Q9P2W1 +ENSG00000131470 PSMC3IP testis round or early spermatids High Enhanced Q9P2W1 +ENSG00000131470 PSMC3IP testis spermatogonia High Enhanced Q9P2W1 +ENSG00000131473 ACLY epididymis glandular cells Low Enhanced P53396 +ENSG00000131473 ACLY prostate glandular cells High Enhanced P53396 +ENSG00000131473 ACLY testis cells in seminiferous ducts Medium Enhanced P53396 +ENSG00000131473 ACLY testis Leydig cells High Enhanced P53396 +ENSG00000131482 G6PC epididymis glandular cells Low Enhanced P35575 +ENSG00000131620 ANO1 epididymis glandular cells Medium Enhanced Q5XXA6 +ENSG00000131620 ANO1 seminal vesicle glandular cells High Enhanced Q5XXA6 +ENSG00000131620 ANO1 testis cells in seminiferous ducts Low Enhanced Q5XXA6 +ENSG00000131711 MAP1B prostate glandular cells Low Enhanced P46821 +ENSG00000131711 MAP1B testis cells in seminiferous ducts Medium Enhanced P46821 +ENSG00000131711 MAP1B testis Leydig cells Low Enhanced P46821 +ENSG00000131721 RHOXF2 testis pachytene spermatocytes Medium Enhanced Q9BQY4 +ENSG00000131721 RHOXF2 testis preleptotene spermatocytes Medium Enhanced Q9BQY4 +ENSG00000131721 RHOXF2 testis spermatogonia High Enhanced Q9BQY4 +ENSG00000131730 CKMT2 epididymis glandular cells Low Enhanced P17540 +ENSG00000131730 CKMT2 seminal vesicle glandular cells Low Enhanced P17540 +ENSG00000131747 TOP2A prostate glandular cells Medium Enhanced P11388 +ENSG00000131747 TOP2A seminal vesicle glandular cells Low Enhanced P11388 +ENSG00000131747 TOP2A testis pachytene spermatocytes High Enhanced P11388 +ENSG00000131747 TOP2A testis preleptotene spermatocytes Medium Enhanced P11388 +ENSG00000131747 TOP2A testis round or early spermatids High Enhanced P11388 +ENSG00000131747 TOP2A testis spermatogonia Low Enhanced P11388 +ENSG00000131773 KHDRBS3 epididymis glandular cells Medium Enhanced O75525 +ENSG00000131773 KHDRBS3 prostate glandular cells Medium Enhanced O75525 +ENSG00000131773 KHDRBS3 seminal vesicle glandular cells Medium Enhanced O75525 +ENSG00000131773 KHDRBS3 testis elongated or late spermatids Medium Enhanced O75525 +ENSG00000131773 KHDRBS3 testis pachytene spermatocytes High Enhanced O75525 +ENSG00000131773 KHDRBS3 testis preleptotene spermatocytes High Enhanced O75525 +ENSG00000131773 KHDRBS3 testis round or early spermatids High Enhanced O75525 +ENSG00000131773 KHDRBS3 testis sertoli cells Medium Enhanced O75525 +ENSG00000131773 KHDRBS3 testis spermatogonia High Enhanced O75525 +ENSG00000131778 CHD1L epididymis glandular cells High Enhanced Q86WJ1 +ENSG00000131778 CHD1L prostate glandular cells Medium Enhanced Q86WJ1 +ENSG00000131778 CHD1L seminal vesicle glandular cells Medium Enhanced Q86WJ1 +ENSG00000131778 CHD1L testis cells in seminiferous ducts High Enhanced Q86WJ1 +ENSG00000131778 CHD1L testis Leydig cells Medium Enhanced Q86WJ1 +ENSG00000131779 PEX11B epididymis glandular cells Medium Supported O96011 +ENSG00000131779 PEX11B prostate glandular cells Medium Supported O96011 +ENSG00000131779 PEX11B seminal vesicle glandular cells Low Supported O96011 +ENSG00000131779 PEX11B testis cells in seminiferous ducts Medium Supported O96011 +ENSG00000131779 PEX11B testis Leydig cells Medium Supported O96011 +ENSG00000131781 FMO5 testis Leydig cells Low Enhanced P49326 +ENSG00000131844 MCCC2 epididymis glandular cells Medium Enhanced Q9HCC0 +ENSG00000131844 MCCC2 prostate glandular cells High Enhanced Q9HCC0 +ENSG00000131844 MCCC2 seminal vesicle glandular cells High Enhanced Q9HCC0 +ENSG00000131844 MCCC2 testis cells in seminiferous ducts Medium Enhanced Q9HCC0 +ENSG00000131844 MCCC2 testis Leydig cells High Enhanced Q9HCC0 +ENSG00000131876 SNRPA1 epididymis glandular cells High Supported P09661 +ENSG00000131876 SNRPA1 prostate glandular cells Medium Supported P09661 +ENSG00000131876 SNRPA1 seminal vesicle glandular cells Medium Supported P09661 +ENSG00000131876 SNRPA1 testis cells in seminiferous ducts High Supported P09661 +ENSG00000131876 SNRPA1 testis Leydig cells Medium Supported P09661 +ENSG00000131899 LLGL1 epididymis glandular cells Medium Enhanced NA +ENSG00000131899 LLGL1 prostate glandular cells Medium Enhanced NA +ENSG00000131899 LLGL1 seminal vesicle glandular cells Medium Enhanced NA +ENSG00000131899 LLGL1 testis cells in seminiferous ducts Medium Enhanced NA +ENSG00000131899 LLGL1 testis Leydig cells Medium Enhanced NA +ENSG00000131914 LIN28A epididymis glandular cells Low Enhanced Q9H9Z2 +ENSG00000131914 LIN28A seminal vesicle glandular cells Low Enhanced Q9H9Z2 +ENSG00000131914 LIN28A testis cells in seminiferous ducts High Enhanced Q9H9Z2 +ENSG00000131981 LGALS3 epididymis glandular cells Medium Enhanced P17931 +ENSG00000131981 LGALS3 prostate glandular cells Medium Enhanced P17931 +ENSG00000131981 LGALS3 seminal vesicle glandular cells Medium Enhanced P17931 +ENSG00000131981 LGALS3 testis cells in seminiferous ducts Medium Enhanced P17931 +ENSG00000131981 LGALS3 testis Leydig cells Medium Enhanced P17931 +ENSG00000132002 DNAJB1 epididymis glandular cells Medium Enhanced P25685 +ENSG00000132002 DNAJB1 prostate glandular cells Medium Enhanced P25685 +ENSG00000132002 DNAJB1 seminal vesicle glandular cells Low Enhanced P25685 +ENSG00000132002 DNAJB1 testis cells in seminiferous ducts High Enhanced P25685 +ENSG00000132002 DNAJB1 testis Leydig cells Medium Enhanced P25685 +ENSG00000132016 C19orf57 prostate glandular cells Medium Enhanced Q0VDD7 +ENSG00000132016 C19orf57 seminal vesicle glandular cells Low Enhanced Q0VDD7 +ENSG00000132016 C19orf57 testis elongated or late spermatids Medium Enhanced Q0VDD7 +ENSG00000132016 C19orf57 testis Leydig cells Low Enhanced Q0VDD7 +ENSG00000132016 C19orf57 testis pachytene spermatocytes Medium Enhanced Q0VDD7 +ENSG00000132016 C19orf57 testis preleptotene spermatocytes High Enhanced Q0VDD7 +ENSG00000132016 C19orf57 testis round or early spermatids Low Enhanced Q0VDD7 +ENSG00000132016 C19orf57 testis spermatogonia High Enhanced Q0VDD7 +ENSG00000132024 CC2D1A epididymis glandular cells Low Supported Q6P1N0 +ENSG00000132024 CC2D1A prostate glandular cells Low Supported Q6P1N0 +ENSG00000132024 CC2D1A seminal vesicle glandular cells Medium Supported Q6P1N0 +ENSG00000132024 CC2D1A testis cells in seminiferous ducts Medium Supported Q6P1N0 +ENSG00000132024 CC2D1A testis Leydig cells Medium Supported Q6P1N0 +ENSG00000132153 DHX30 epididymis glandular cells Low Supported Q7L2E3 +ENSG00000132153 DHX30 seminal vesicle glandular cells Low Supported Q7L2E3 +ENSG00000132153 DHX30 testis cells in seminiferous ducts Medium Supported Q7L2E3 +ENSG00000132153 DHX30 testis Leydig cells Medium Supported Q7L2E3 +ENSG00000132199 ENOSF1 epididymis glandular cells Medium Enhanced Q7L5Y1 +ENSG00000132199 ENOSF1 prostate glandular cells Low Enhanced Q7L5Y1 +ENSG00000132199 ENOSF1 seminal vesicle glandular cells Medium Enhanced Q7L5Y1 +ENSG00000132199 ENOSF1 testis cells in seminiferous ducts Low Enhanced Q7L5Y1 +ENSG00000132199 ENOSF1 testis Leydig cells Medium Enhanced Q7L5Y1 +ENSG00000132205 EMILIN2 epididymis glandular cells Low Supported Q9BXX0 +ENSG00000132205 EMILIN2 prostate glandular cells Low Supported Q9BXX0 +ENSG00000132205 EMILIN2 testis cells in seminiferous ducts Low Supported Q9BXX0 +ENSG00000132275 RRP8 epididymis glandular cells High Supported O43159 +ENSG00000132275 RRP8 prostate glandular cells High Supported O43159 +ENSG00000132275 RRP8 seminal vesicle glandular cells Medium Supported O43159 +ENSG00000132275 RRP8 testis cells in seminiferous ducts Medium Supported O43159 +ENSG00000132275 RRP8 testis Leydig cells Medium Supported O43159 +ENSG00000132294 EFR3A epididymis glandular cells Medium Enhanced Q14156 +ENSG00000132294 EFR3A prostate glandular cells Low Enhanced Q14156 +ENSG00000132294 EFR3A seminal vesicle glandular cells Medium Enhanced Q14156 +ENSG00000132294 EFR3A testis cells in seminiferous ducts High Enhanced Q14156 +ENSG00000132294 EFR3A testis Leydig cells High Enhanced Q14156 +ENSG00000132300 PTCD3 prostate glandular cells Medium Supported Q96EY7 +ENSG00000132300 PTCD3 seminal vesicle glandular cells High Supported Q96EY7 +ENSG00000132300 PTCD3 testis cells in seminiferous ducts Medium Supported Q96EY7 +ENSG00000132300 PTCD3 testis Leydig cells High Supported Q96EY7 +ENSG00000132305 IMMT seminal vesicle glandular cells Medium Enhanced Q16891 +ENSG00000132305 IMMT testis cells in seminiferous ducts Medium Enhanced Q16891 +ENSG00000132305 IMMT testis Leydig cells Medium Enhanced Q16891 +ENSG00000132326 PER2 epididymis glandular cells Medium Enhanced O15055 +ENSG00000132326 PER2 prostate glandular cells Low Enhanced O15055 +ENSG00000132326 PER2 seminal vesicle glandular cells Medium Enhanced O15055 +ENSG00000132326 PER2 testis cells in seminiferous ducts High Enhanced O15055 +ENSG00000132326 PER2 testis Leydig cells Medium Enhanced O15055 +ENSG00000132334 PTPRE epididymis glandular cells High Supported P23469 +ENSG00000132334 PTPRE testis cells in seminiferous ducts Low Supported P23469 +ENSG00000132334 PTPRE testis Leydig cells Low Supported P23469 +ENSG00000132356 PRKAA1 epididymis glandular cells Medium Supported Q13131 +ENSG00000132356 PRKAA1 prostate glandular cells Low Supported Q13131 +ENSG00000132356 PRKAA1 testis cells in seminiferous ducts Medium Supported Q13131 +ENSG00000132356 PRKAA1 testis Leydig cells Medium Supported Q13131 +ENSG00000132382 MYBBP1A epididymis glandular cells High Supported Q9BQG0 +ENSG00000132382 MYBBP1A prostate glandular cells Medium Supported Q9BQG0 +ENSG00000132382 MYBBP1A seminal vesicle glandular cells Low Supported Q9BQG0 +ENSG00000132382 MYBBP1A testis cells in seminiferous ducts High Supported Q9BQG0 +ENSG00000132382 MYBBP1A testis Leydig cells High Supported Q9BQG0 +ENSG00000132383 RPA1 epididymis glandular cells High Supported P27694 +ENSG00000132383 RPA1 prostate glandular cells Medium Supported P27694 +ENSG00000132383 RPA1 seminal vesicle glandular cells Medium Supported P27694 +ENSG00000132383 RPA1 testis cells in seminiferous ducts High Supported P27694 +ENSG00000132383 RPA1 testis Leydig cells Medium Supported P27694 +ENSG00000132423 COQ3 prostate glandular cells Low Enhanced Q9NZJ6 +ENSG00000132423 COQ3 seminal vesicle glandular cells Medium Enhanced Q9NZJ6 +ENSG00000132423 COQ3 testis cells in seminiferous ducts Low Enhanced Q9NZJ6 +ENSG00000132423 COQ3 testis Leydig cells Medium Enhanced Q9NZJ6 +ENSG00000132437 DDC prostate glandular cells Low Enhanced P20711 +ENSG00000132437 DDC seminal vesicle glandular cells Low Enhanced P20711 +ENSG00000132437 DDC testis cells in seminiferous ducts Low Enhanced P20711 +ENSG00000132437 DDC testis Leydig cells Low Enhanced P20711 +ENSG00000132463 GRSF1 epididymis glandular cells Medium Enhanced Q12849 +ENSG00000132463 GRSF1 prostate glandular cells Medium Enhanced Q12849 +ENSG00000132463 GRSF1 seminal vesicle glandular cells Medium Enhanced Q12849 +ENSG00000132463 GRSF1 testis cells in seminiferous ducts Medium Enhanced Q12849 +ENSG00000132463 GRSF1 testis Leydig cells Medium Enhanced Q12849 +ENSG00000132470 ITGB4 epididymis glandular cells Low Enhanced P16144 +ENSG00000132470 ITGB4 prostate glandular cells Low Enhanced P16144 +ENSG00000132470 ITGB4 seminal vesicle glandular cells Low Enhanced P16144 +ENSG00000132470 ITGB4 testis cells in seminiferous ducts Medium Enhanced P16144 +ENSG00000132470 ITGB4 testis Leydig cells Low Enhanced P16144 +ENSG00000132475 H3F3B epididymis glandular cells High Supported K7EK07 +ENSG00000132475 H3F3B prostate glandular cells High Supported K7EK07 +ENSG00000132475 H3F3B seminal vesicle glandular cells High Supported K7EK07 +ENSG00000132475 H3F3B testis cells in seminiferous ducts High Supported K7EK07 +ENSG00000132475 H3F3B testis Leydig cells High Supported K7EK07 +ENSG00000132485 ZRANB2 epididymis glandular cells High Supported O95218 +ENSG00000132485 ZRANB2 prostate glandular cells Medium Supported O95218 +ENSG00000132485 ZRANB2 seminal vesicle glandular cells Medium Supported O95218 +ENSG00000132485 ZRANB2 testis cells in seminiferous ducts High Supported O95218 +ENSG00000132485 ZRANB2 testis Leydig cells High Supported O95218 +ENSG00000132510 KDM6B epididymis glandular cells Medium Enhanced O15054 +ENSG00000132510 KDM6B prostate glandular cells Medium Enhanced O15054 +ENSG00000132510 KDM6B seminal vesicle glandular cells Medium Enhanced O15054 +ENSG00000132510 KDM6B testis cells in seminiferous ducts Medium Enhanced O15054 +ENSG00000132510 KDM6B testis Leydig cells Medium Enhanced O15054 +ENSG00000132541 RIDA seminal vesicle glandular cells Low Enhanced P52758 +ENSG00000132541 RIDA testis Leydig cells Low Enhanced P52758 +ENSG00000132563 REEP2 testis cells in seminiferous ducts Low Enhanced Q9BRK0 +ENSG00000132589 FLOT2 epididymis glandular cells Medium Enhanced Q14254 +ENSG00000132589 FLOT2 prostate glandular cells High Enhanced Q14254 +ENSG00000132589 FLOT2 seminal vesicle glandular cells Medium Enhanced Q14254 +ENSG00000132589 FLOT2 testis cells in seminiferous ducts Low Enhanced Q14254 +ENSG00000132589 FLOT2 testis Leydig cells Medium Enhanced Q14254 +ENSG00000132591 ERAL1 epididymis glandular cells Medium Supported O75616 +ENSG00000132591 ERAL1 prostate glandular cells Medium Supported O75616 +ENSG00000132591 ERAL1 seminal vesicle glandular cells Medium Supported O75616 +ENSG00000132591 ERAL1 testis cells in seminiferous ducts Medium Supported O75616 +ENSG00000132591 ERAL1 testis Leydig cells Medium Supported O75616 +ENSG00000132600 PRMT7 epididymis glandular cells Medium Supported Q9NVM4 +ENSG00000132600 PRMT7 prostate glandular cells Medium Supported Q9NVM4 +ENSG00000132600 PRMT7 seminal vesicle glandular cells Medium Supported Q9NVM4 +ENSG00000132600 PRMT7 testis cells in seminiferous ducts High Supported Q9NVM4 +ENSG00000132600 PRMT7 testis Leydig cells High Supported Q9NVM4 +ENSG00000132603 NIP7 epididymis glandular cells Medium Enhanced Q9Y221 +ENSG00000132603 NIP7 prostate glandular cells Medium Enhanced Q9Y221 +ENSG00000132603 NIP7 seminal vesicle glandular cells Medium Enhanced Q9Y221 +ENSG00000132603 NIP7 testis cells in seminiferous ducts Medium Enhanced Q9Y221 +ENSG00000132603 NIP7 testis Leydig cells Medium Enhanced Q9Y221 +ENSG00000132604 TERF2 epididymis glandular cells Medium Enhanced Q15554 +ENSG00000132604 TERF2 prostate glandular cells Medium Enhanced Q15554 +ENSG00000132604 TERF2 seminal vesicle glandular cells Medium Enhanced Q15554 +ENSG00000132604 TERF2 testis cells in seminiferous ducts Medium Enhanced Q15554 +ENSG00000132604 TERF2 testis Leydig cells Medium Enhanced Q15554 +ENSG00000132646 PCNA epididymis glandular cells Medium Enhanced P12004 +ENSG00000132646 PCNA prostate glandular cells Medium Enhanced P12004 +ENSG00000132646 PCNA seminal vesicle glandular cells Medium Enhanced P12004 +ENSG00000132646 PCNA testis cells in seminiferous ducts Medium Enhanced P12004 +ENSG00000132646 PCNA testis Leydig cells Medium Enhanced P12004 +ENSG00000132677 RHBG prostate glandular cells Low Enhanced Q9H310 +ENSG00000132694 ARHGEF11 epididymis glandular cells Medium Enhanced O15085 +ENSG00000132694 ARHGEF11 prostate glandular cells Medium Enhanced O15085 +ENSG00000132694 ARHGEF11 seminal vesicle glandular cells High Enhanced O15085 +ENSG00000132694 ARHGEF11 testis cells in seminiferous ducts High Enhanced O15085 +ENSG00000132694 ARHGEF11 testis Leydig cells Medium Enhanced O15085 +ENSG00000132698 RAB25 epididymis glandular cells High Enhanced P57735 +ENSG00000132698 RAB25 prostate glandular cells High Enhanced P57735 +ENSG00000132698 RAB25 seminal vesicle glandular cells High Enhanced P57735 +ENSG00000132773 TOE1 epididymis glandular cells High Enhanced Q96GM8 +ENSG00000132773 TOE1 prostate glandular cells Medium Enhanced Q96GM8 +ENSG00000132773 TOE1 seminal vesicle glandular cells Medium Enhanced Q96GM8 +ENSG00000132773 TOE1 testis cells in seminiferous ducts High Enhanced Q96GM8 +ENSG00000132773 TOE1 testis Leydig cells Medium Enhanced Q96GM8 +ENSG00000132780 NASP epididymis glandular cells Low Enhanced P49321 +ENSG00000132780 NASP prostate glandular cells Low Enhanced P49321 +ENSG00000132780 NASP seminal vesicle glandular cells Medium Enhanced P49321 +ENSG00000132780 NASP testis cells in seminiferous ducts High Enhanced P49321 +ENSG00000132780 NASP testis Leydig cells Low Enhanced P49321 +ENSG00000132911 NMUR2 testis elongated or late spermatids High Enhanced Q9GZQ4 +ENSG00000132911 NMUR2 testis Leydig cells Low Enhanced Q9GZQ4 +ENSG00000132911 NMUR2 testis pachytene spermatocytes High Enhanced Q9GZQ4 +ENSG00000132911 NMUR2 testis preleptotene spermatocytes Low Enhanced Q9GZQ4 +ENSG00000132911 NMUR2 testis round or early spermatids Medium Enhanced Q9GZQ4 +ENSG00000132911 NMUR2 testis sertoli cells Low Enhanced Q9GZQ4 +ENSG00000132911 NMUR2 testis spermatogonia Low Enhanced Q9GZQ4 +ENSG00000132938 MTUS2 epididymis glandular cells Medium Enhanced Q5JR59 +ENSG00000132938 MTUS2 prostate glandular cells Low Enhanced Q5JR59 +ENSG00000132938 MTUS2 seminal vesicle glandular cells Medium Enhanced Q5JR59 +ENSG00000132938 MTUS2 testis cells in seminiferous ducts Medium Enhanced Q5JR59 +ENSG00000132938 MTUS2 testis Leydig cells Medium Enhanced Q5JR59 +ENSG00000133020 MYH8 epididymis glandular cells Low Enhanced P13535 +ENSG00000133020 MYH8 seminal vesicle glandular cells Low Enhanced P13535 +ENSG00000133020 MYH8 testis cells in seminiferous ducts Low Enhanced P13535 +ENSG00000133020 MYH8 testis Leydig cells Low Enhanced P13535 +ENSG00000133026 MYH10 epididymis glandular cells Medium Enhanced P35580 +ENSG00000133026 MYH10 prostate glandular cells Medium Enhanced P35580 +ENSG00000133026 MYH10 seminal vesicle glandular cells Medium Enhanced P35580 +ENSG00000133026 MYH10 testis cells in seminiferous ducts Medium Enhanced P35580 +ENSG00000133026 MYH10 testis Leydig cells Low Enhanced P35580 +ENSG00000133028 SCO1 epididymis glandular cells Low Enhanced O75880 +ENSG00000133028 SCO1 prostate glandular cells Low Enhanced O75880 +ENSG00000133028 SCO1 seminal vesicle glandular cells Medium Enhanced O75880 +ENSG00000133028 SCO1 testis cells in seminiferous ducts Medium Enhanced O75880 +ENSG00000133028 SCO1 testis Leydig cells Medium Enhanced O75880 +ENSG00000133030 MPRIP epididymis glandular cells High Enhanced Q6WCQ1 +ENSG00000133030 MPRIP prostate glandular cells Low Enhanced Q6WCQ1 +ENSG00000133030 MPRIP seminal vesicle glandular cells Medium Enhanced Q6WCQ1 +ENSG00000133030 MPRIP testis cells in seminiferous ducts Medium Enhanced Q6WCQ1 +ENSG00000133030 MPRIP testis Leydig cells Medium Enhanced Q6WCQ1 +ENSG00000133110 POSTN epididymis glandular cells Medium Enhanced Q15063 +ENSG00000133110 POSTN testis cells in seminiferous ducts Low Enhanced Q15063 +ENSG00000133121 STARD13 epididymis glandular cells Medium Enhanced Q9Y3M8 +ENSG00000133121 STARD13 prostate glandular cells Medium Enhanced Q9Y3M8 +ENSG00000133121 STARD13 seminal vesicle glandular cells Medium Enhanced Q9Y3M8 +ENSG00000133121 STARD13 testis cells in seminiferous ducts Medium Enhanced Q9Y3M8 +ENSG00000133121 STARD13 testis Leydig cells Medium Enhanced Q9Y3M8 +ENSG00000133131 MORC4 testis cells in seminiferous ducts Medium Enhanced Q8TE76 +ENSG00000133138 TBC1D8B epididymis glandular cells Medium Enhanced Q0IIM8 +ENSG00000133138 TBC1D8B prostate glandular cells Low Enhanced Q0IIM8 +ENSG00000133138 TBC1D8B seminal vesicle glandular cells Medium Enhanced Q0IIM8 +ENSG00000133138 TBC1D8B testis cells in seminiferous ducts Low Enhanced Q0IIM8 +ENSG00000133138 TBC1D8B testis Leydig cells Medium Enhanced Q0IIM8 +ENSG00000133226 SRRM1 epididymis glandular cells High Supported Q8IYB3 +ENSG00000133226 SRRM1 prostate glandular cells High Supported Q8IYB3 +ENSG00000133226 SRRM1 seminal vesicle glandular cells High Supported Q8IYB3 +ENSG00000133226 SRRM1 testis cells in seminiferous ducts High Supported Q8IYB3 +ENSG00000133226 SRRM1 testis Leydig cells Medium Supported Q8IYB3 +ENSG00000133265 HSPBP1 epididymis glandular cells Medium Enhanced Q9NZL4 +ENSG00000133265 HSPBP1 prostate glandular cells Medium Enhanced Q9NZL4 +ENSG00000133265 HSPBP1 seminal vesicle glandular cells Medium Enhanced Q9NZL4 +ENSG00000133265 HSPBP1 testis cells in seminiferous ducts High Enhanced Q9NZL4 +ENSG00000133265 HSPBP1 testis Leydig cells Low Enhanced Q9NZL4 +ENSG00000133313 CNDP2 epididymis glandular cells Medium Enhanced Q96KP4 +ENSG00000133313 CNDP2 prostate glandular cells High Enhanced Q96KP4 +ENSG00000133313 CNDP2 seminal vesicle glandular cells Medium Enhanced Q96KP4 +ENSG00000133313 CNDP2 testis cells in seminiferous ducts Low Enhanced Q96KP4 +ENSG00000133313 CNDP2 testis Leydig cells Medium Enhanced Q96KP4 +ENSG00000133393 FOPNL epididymis glandular cells Medium Supported NA +ENSG00000133393 FOPNL prostate glandular cells Low Supported NA +ENSG00000133393 FOPNL seminal vesicle glandular cells Low Supported NA +ENSG00000133393 FOPNL testis cells in seminiferous ducts Low Supported NA +ENSG00000133393 FOPNL testis Leydig cells Low Supported NA +ENSG00000133422 MORC2 epididymis glandular cells Low Enhanced Q9Y6X9 +ENSG00000133422 MORC2 prostate glandular cells Low Enhanced Q9Y6X9 +ENSG00000133422 MORC2 seminal vesicle glandular cells Medium Enhanced Q9Y6X9 +ENSG00000133422 MORC2 testis cells in seminiferous ducts High Enhanced Q9Y6X9 +ENSG00000133422 MORC2 testis Leydig cells Low Enhanced Q9Y6X9 +ENSG00000133475 GGT2 epididymis glandular cells Medium Supported P36268 +ENSG00000133475 GGT2 prostate glandular cells Low Supported P36268 +ENSG00000133475 GGT2 seminal vesicle glandular cells Low Supported P36268 +ENSG00000133477 FAM83F epididymis glandular cells Medium Enhanced Q8NEG4 +ENSG00000133477 FAM83F prostate glandular cells Low Enhanced Q8NEG4 +ENSG00000133477 FAM83F seminal vesicle glandular cells Low Enhanced Q8NEG4 +ENSG00000133477 FAM83F testis elongated or late spermatids Low Enhanced Q8NEG4 +ENSG00000133477 FAM83F testis Leydig cells Low Enhanced Q8NEG4 +ENSG00000133477 FAM83F testis pachytene spermatocytes Low Enhanced Q8NEG4 +ENSG00000133477 FAM83F testis peritubular cells Low Enhanced Q8NEG4 +ENSG00000133477 FAM83F testis preleptotene spermatocytes High Enhanced Q8NEG4 +ENSG00000133477 FAM83F testis round or early spermatids Low Enhanced Q8NEG4 +ENSG00000133477 FAM83F testis spermatogonia High Enhanced Q8NEG4 +ENSG00000133574 GIMAP4 prostate glandular cells Low Enhanced Q9NUV9 +ENSG00000133574 GIMAP4 seminal vesicle glandular cells Medium Enhanced Q9NUV9 +ENSG00000133574 GIMAP4 testis cells in seminiferous ducts Medium Enhanced Q9NUV9 +ENSG00000133574 GIMAP4 testis Leydig cells Low Enhanced Q9NUV9 +ENSG00000133706 LARS epididymis glandular cells High Supported Q9P2J5 +ENSG00000133706 LARS prostate glandular cells High Supported Q9P2J5 +ENSG00000133706 LARS seminal vesicle glandular cells High Supported Q9P2J5 +ENSG00000133706 LARS testis cells in seminiferous ducts Low Supported Q9P2J5 +ENSG00000133706 LARS testis Leydig cells Low Supported Q9P2J5 +ENSG00000133794 ARNTL epididymis glandular cells Medium Supported O00327 +ENSG00000133794 ARNTL prostate glandular cells High Supported O00327 +ENSG00000133794 ARNTL seminal vesicle glandular cells Medium Supported O00327 +ENSG00000133794 ARNTL testis cells in seminiferous ducts Medium Supported O00327 +ENSG00000133794 ARNTL testis Leydig cells Medium Supported O00327 +ENSG00000133835 HSD17B4 epididymis glandular cells High Enhanced P51659 +ENSG00000133835 HSD17B4 prostate glandular cells Medium Enhanced P51659 +ENSG00000133835 HSD17B4 seminal vesicle glandular cells Medium Enhanced P51659 +ENSG00000133835 HSD17B4 testis cells in seminiferous ducts Medium Enhanced P51659 +ENSG00000133835 HSD17B4 testis Leydig cells Medium Enhanced P51659 +ENSG00000133858 ZFC3H1 epididymis glandular cells High Enhanced O60293 +ENSG00000133858 ZFC3H1 prostate glandular cells Medium Enhanced O60293 +ENSG00000133858 ZFC3H1 seminal vesicle glandular cells Medium Enhanced O60293 +ENSG00000133858 ZFC3H1 testis cells in seminiferous ducts High Enhanced O60293 +ENSG00000133858 ZFC3H1 testis Leydig cells High Enhanced O60293 +ENSG00000133863 TEX15 testis elongated or late spermatids Medium Enhanced Q9BXT5 +ENSG00000133863 TEX15 testis pachytene spermatocytes Low Enhanced Q9BXT5 +ENSG00000133863 TEX15 testis preleptotene spermatocytes Medium Enhanced Q9BXT5 +ENSG00000133863 TEX15 testis round or early spermatids Medium Enhanced Q9BXT5 +ENSG00000133863 TEX15 testis spermatogonia Medium Enhanced Q9BXT5 +ENSG00000134001 EIF2S1 epididymis glandular cells Medium Supported P05198 +ENSG00000134001 EIF2S1 prostate glandular cells Medium Supported P05198 +ENSG00000134001 EIF2S1 seminal vesicle glandular cells Medium Supported P05198 +ENSG00000134001 EIF2S1 testis cells in seminiferous ducts Medium Supported P05198 +ENSG00000134001 EIF2S1 testis Leydig cells Medium Supported P05198 +ENSG00000134007 ADAM20 testis elongated or late spermatids High Enhanced O43506 +ENSG00000134007 ADAM20 testis Leydig cells Low Enhanced O43506 +ENSG00000134007 ADAM20 testis pachytene spermatocytes Low Enhanced O43506 +ENSG00000134007 ADAM20 testis preleptotene spermatocytes Low Enhanced O43506 +ENSG00000134007 ADAM20 testis round or early spermatids Low Enhanced O43506 +ENSG00000134007 ADAM20 testis spermatogonia Medium Enhanced O43506 +ENSG00000134049 IER3IP1 epididymis glandular cells Medium Supported Q9Y5U9 +ENSG00000134049 IER3IP1 prostate glandular cells Medium Supported Q9Y5U9 +ENSG00000134049 IER3IP1 seminal vesicle glandular cells Medium Supported Q9Y5U9 +ENSG00000134049 IER3IP1 testis cells in seminiferous ducts Medium Supported Q9Y5U9 +ENSG00000134049 IER3IP1 testis Leydig cells High Supported Q9Y5U9 +ENSG00000134056 MRPS36 epididymis glandular cells High Supported NA +ENSG00000134056 MRPS36 prostate glandular cells High Supported NA +ENSG00000134056 MRPS36 seminal vesicle glandular cells High Supported NA +ENSG00000134056 MRPS36 testis cells in seminiferous ducts Medium Supported NA +ENSG00000134056 MRPS36 testis Leydig cells High Supported NA +ENSG00000134057 CCNB1 seminal vesicle glandular cells Medium Enhanced P14635 +ENSG00000134057 CCNB1 testis cells in seminiferous ducts High Enhanced P14635 +ENSG00000134058 CDK7 epididymis glandular cells High Enhanced NA +ENSG00000134058 CDK7 prostate glandular cells Medium Enhanced NA +ENSG00000134058 CDK7 seminal vesicle glandular cells Low Enhanced NA +ENSG00000134058 CDK7 testis cells in seminiferous ducts Medium Enhanced NA +ENSG00000134058 CDK7 testis Leydig cells Low Enhanced NA +ENSG00000134121 CHL1 prostate glandular cells Low Enhanced O00533 +ENSG00000134121 CHL1 testis Leydig cells Low Enhanced O00533 +ENSG00000134138 MEIS2 epididymis glandular cells Low Enhanced O14770 +ENSG00000134138 MEIS2 prostate glandular cells Low Enhanced O14770 +ENSG00000134138 MEIS2 seminal vesicle glandular cells Medium Enhanced O14770 +ENSG00000134138 MEIS2 testis cells in seminiferous ducts Low Enhanced O14770 +ENSG00000134138 MEIS2 testis Leydig cells High Enhanced O14770 +ENSG00000134202 GSTM3 epididymis glandular cells Medium Enhanced P21266 +ENSG00000134202 GSTM3 seminal vesicle glandular cells Medium Enhanced P21266 +ENSG00000134202 GSTM3 testis cells in seminiferous ducts High Enhanced P21266 +ENSG00000134202 GSTM3 testis Leydig cells Medium Enhanced P21266 +ENSG00000134240 HMGCS2 testis cells in seminiferous ducts Medium Enhanced P54868 +ENSG00000134265 NAPG epididymis glandular cells Medium Enhanced Q99747 +ENSG00000134265 NAPG prostate glandular cells Medium Enhanced Q99747 +ENSG00000134265 NAPG seminal vesicle glandular cells Medium Enhanced Q99747 +ENSG00000134265 NAPG testis cells in seminiferous ducts Medium Enhanced Q99747 +ENSG00000134265 NAPG testis Leydig cells Medium Enhanced Q99747 +ENSG00000134283 PPHLN1 epididymis glandular cells Medium Enhanced Q8NEY8 +ENSG00000134283 PPHLN1 prostate glandular cells Low Enhanced Q8NEY8 +ENSG00000134283 PPHLN1 seminal vesicle glandular cells High Enhanced Q8NEY8 +ENSG00000134283 PPHLN1 testis cells in seminiferous ducts High Enhanced Q8NEY8 +ENSG00000134283 PPHLN1 testis Leydig cells Medium Enhanced Q8NEY8 +ENSG00000134285 FKBP11 epididymis glandular cells Medium Enhanced Q9NYL4 +ENSG00000134285 FKBP11 seminal vesicle glandular cells High Enhanced Q9NYL4 +ENSG00000134285 FKBP11 testis cells in seminiferous ducts Low Enhanced Q9NYL4 +ENSG00000134291 TMEM106C epididymis glandular cells Medium Enhanced Q9BVX2 +ENSG00000134291 TMEM106C prostate glandular cells Medium Enhanced Q9BVX2 +ENSG00000134291 TMEM106C seminal vesicle glandular cells Medium Enhanced Q9BVX2 +ENSG00000134291 TMEM106C testis cells in seminiferous ducts Medium Enhanced Q9BVX2 +ENSG00000134291 TMEM106C testis Leydig cells Medium Enhanced Q9BVX2 +ENSG00000134313 KIDINS220 epididymis glandular cells Medium Supported Q9ULH0 +ENSG00000134313 KIDINS220 prostate glandular cells Medium Supported Q9ULH0 +ENSG00000134313 KIDINS220 seminal vesicle glandular cells Medium Supported Q9ULH0 +ENSG00000134313 KIDINS220 testis Leydig cells Low Supported Q9ULH0 +ENSG00000134317 GRHL1 seminal vesicle glandular cells Low Enhanced Q9NZI5 +ENSG00000134317 GRHL1 testis cells in seminiferous ducts Medium Enhanced Q9NZI5 +ENSG00000134317 GRHL1 testis Leydig cells High Enhanced Q9NZI5 +ENSG00000134369 NAV1 epididymis glandular cells Medium Enhanced Q8NEY1 +ENSG00000134369 NAV1 prostate glandular cells Medium Enhanced Q8NEY1 +ENSG00000134369 NAV1 seminal vesicle glandular cells Medium Enhanced Q8NEY1 +ENSG00000134369 NAV1 testis cells in seminiferous ducts High Enhanced Q8NEY1 +ENSG00000134369 NAV1 testis Leydig cells Medium Enhanced Q8NEY1 +ENSG00000134371 CDC73 epididymis glandular cells Medium Enhanced Q6P1J9 +ENSG00000134371 CDC73 seminal vesicle glandular cells Low Enhanced Q6P1J9 +ENSG00000134371 CDC73 testis cells in seminiferous ducts High Enhanced Q6P1J9 +ENSG00000134371 CDC73 testis Leydig cells Low Enhanced Q6P1J9 +ENSG00000134419 RPS15A epididymis glandular cells Medium Supported P62244 +ENSG00000134419 RPS15A prostate glandular cells Medium Supported P62244 +ENSG00000134419 RPS15A seminal vesicle glandular cells Medium Supported P62244 +ENSG00000134419 RPS15A testis cells in seminiferous ducts Medium Supported P62244 +ENSG00000134419 RPS15A testis Leydig cells Medium Supported P62244 +ENSG00000134440 NARS epididymis glandular cells Medium Enhanced O43776 +ENSG00000134440 NARS prostate glandular cells Medium Enhanced O43776 +ENSG00000134440 NARS seminal vesicle glandular cells Medium Enhanced O43776 +ENSG00000134440 NARS testis cells in seminiferous ducts Medium Enhanced O43776 +ENSG00000134440 NARS testis Leydig cells Medium Enhanced O43776 +ENSG00000134452 FBXO18 epididymis glandular cells High Supported Q8NFZ0 +ENSG00000134452 FBXO18 prostate glandular cells High Supported Q8NFZ0 +ENSG00000134452 FBXO18 seminal vesicle glandular cells High Supported Q8NFZ0 +ENSG00000134452 FBXO18 testis cells in seminiferous ducts High Supported Q8NFZ0 +ENSG00000134452 FBXO18 testis Leydig cells High Supported Q8NFZ0 +ENSG00000134453 RBM17 epididymis glandular cells High Supported Q96I25 +ENSG00000134453 RBM17 prostate glandular cells High Supported Q96I25 +ENSG00000134453 RBM17 seminal vesicle glandular cells High Supported Q96I25 +ENSG00000134453 RBM17 testis cells in seminiferous ducts High Supported Q96I25 +ENSG00000134453 RBM17 testis Leydig cells High Supported Q96I25 +ENSG00000134463 ECHDC3 epididymis glandular cells Medium Enhanced Q96DC8 +ENSG00000134463 ECHDC3 prostate glandular cells Medium Enhanced Q96DC8 +ENSG00000134463 ECHDC3 seminal vesicle glandular cells High Enhanced Q96DC8 +ENSG00000134463 ECHDC3 testis cells in seminiferous ducts Medium Enhanced Q96DC8 +ENSG00000134463 ECHDC3 testis Leydig cells Medium Enhanced Q96DC8 +ENSG00000134574 DDB2 epididymis glandular cells Medium Enhanced Q92466 +ENSG00000134574 DDB2 seminal vesicle glandular cells Medium Enhanced Q92466 +ENSG00000134574 DDB2 testis cells in seminiferous ducts Low Enhanced Q92466 +ENSG00000134574 DDB2 testis Leydig cells Medium Enhanced Q92466 +ENSG00000134627 PIWIL4 epididymis glandular cells Low Enhanced Q7Z3Z4 +ENSG00000134627 PIWIL4 prostate glandular cells Low Enhanced Q7Z3Z4 +ENSG00000134627 PIWIL4 seminal vesicle glandular cells Low Enhanced Q7Z3Z4 +ENSG00000134627 PIWIL4 testis elongated or late spermatids High Enhanced Q7Z3Z4 +ENSG00000134627 PIWIL4 testis Leydig cells Low Enhanced Q7Z3Z4 +ENSG00000134627 PIWIL4 testis pachytene spermatocytes High Enhanced Q7Z3Z4 +ENSG00000134627 PIWIL4 testis preleptotene spermatocytes Medium Enhanced Q7Z3Z4 +ENSG00000134627 PIWIL4 testis round or early spermatids Medium Enhanced Q7Z3Z4 +ENSG00000134627 PIWIL4 testis spermatogonia Medium Enhanced Q7Z3Z4 +ENSG00000134668 SPOCD1 testis peritubular cells Low Enhanced Q6ZMY3 +ENSG00000134668 SPOCD1 testis preleptotene spermatocytes Medium Enhanced Q6ZMY3 +ENSG00000134668 SPOCD1 testis spermatogonia High Enhanced Q6ZMY3 +ENSG00000134684 YARS epididymis glandular cells Medium Enhanced P54577 +ENSG00000134684 YARS prostate glandular cells Medium Enhanced P54577 +ENSG00000134684 YARS seminal vesicle glandular cells Medium Enhanced P54577 +ENSG00000134684 YARS testis cells in seminiferous ducts High Enhanced P54577 +ENSG00000134684 YARS testis Leydig cells Medium Enhanced P54577 +ENSG00000134686 PHC2 epididymis glandular cells Medium Supported Q8IXK0 +ENSG00000134686 PHC2 prostate glandular cells High Supported Q8IXK0 +ENSG00000134686 PHC2 seminal vesicle glandular cells Medium Supported Q8IXK0 +ENSG00000134686 PHC2 testis cells in seminiferous ducts Medium Supported Q8IXK0 +ENSG00000134686 PHC2 testis Leydig cells Medium Supported Q8IXK0 +ENSG00000134690 CDCA8 epididymis glandular cells Low Enhanced Q53HL2 +ENSG00000134690 CDCA8 prostate glandular cells Low Enhanced Q53HL2 +ENSG00000134690 CDCA8 testis cells in seminiferous ducts High Enhanced Q53HL2 +ENSG00000134690 CDCA8 testis Leydig cells Low Enhanced Q53HL2 +ENSG00000134709 HOOK1 testis cells in seminiferous ducts Low Enhanced Q9UJC3 +ENSG00000134709 HOOK1 testis Leydig cells Low Enhanced Q9UJC3 +ENSG00000134744 ZCCHC11 prostate glandular cells Low Supported Q5TAX3 +ENSG00000134744 ZCCHC11 testis Leydig cells Low Supported Q5TAX3 +ENSG00000134755 DSC2 epididymis glandular cells Low Enhanced Q02487 +ENSG00000134755 DSC2 prostate glandular cells Medium Enhanced Q02487 +ENSG00000134755 DSC2 seminal vesicle glandular cells Low Enhanced Q02487 +ENSG00000134760 DSG1 seminal vesicle glandular cells Low Enhanced Q02413 +ENSG00000134760 DSG1 testis cells in seminiferous ducts Medium Enhanced Q02413 +ENSG00000134760 DSG1 testis Leydig cells Medium Enhanced Q02413 +ENSG00000134769 DTNA seminal vesicle glandular cells Low Enhanced Q9Y4J8 +ENSG00000134769 DTNA testis cells in seminiferous ducts Low Enhanced Q9Y4J8 +ENSG00000134769 DTNA testis Leydig cells Low Enhanced Q9Y4J8 +ENSG00000134809 TIMM10 epididymis glandular cells High Enhanced P62072 +ENSG00000134809 TIMM10 prostate glandular cells High Enhanced P62072 +ENSG00000134809 TIMM10 seminal vesicle glandular cells High Enhanced P62072 +ENSG00000134809 TIMM10 testis cells in seminiferous ducts High Enhanced P62072 +ENSG00000134809 TIMM10 testis Leydig cells High Enhanced P62072 +ENSG00000134812 GIF epididymis glandular cells Low Enhanced P27352 +ENSG00000134812 GIF seminal vesicle glandular cells Low Enhanced P27352 +ENSG00000134812 GIF testis cells in seminiferous ducts Low Enhanced P27352 +ENSG00000134851 TMEM165 epididymis glandular cells High Supported Q9HC07 +ENSG00000134851 TMEM165 prostate glandular cells High Supported Q9HC07 +ENSG00000134851 TMEM165 seminal vesicle glandular cells High Supported Q9HC07 +ENSG00000134851 TMEM165 testis cells in seminiferous ducts Medium Supported Q9HC07 +ENSG00000134851 TMEM165 testis Leydig cells High Supported Q9HC07 +ENSG00000134852 CLOCK epididymis glandular cells Medium Supported O15516 +ENSG00000134852 CLOCK prostate glandular cells Medium Supported O15516 +ENSG00000134852 CLOCK seminal vesicle glandular cells Medium Supported O15516 +ENSG00000134852 CLOCK testis cells in seminiferous ducts Medium Supported O15516 +ENSG00000134852 CLOCK testis Leydig cells Low Supported O15516 +ENSG00000134884 ARGLU1 epididymis glandular cells High Supported Q9NWB6 +ENSG00000134884 ARGLU1 prostate glandular cells Medium Supported Q9NWB6 +ENSG00000134884 ARGLU1 seminal vesicle glandular cells High Supported Q9NWB6 +ENSG00000134884 ARGLU1 testis cells in seminiferous ducts High Supported Q9NWB6 +ENSG00000134884 ARGLU1 testis Leydig cells Medium Supported Q9NWB6 +ENSG00000134899 ERCC5 epididymis glandular cells Medium Supported P28715 +ENSG00000134899 ERCC5 prostate glandular cells Medium Supported P28715 +ENSG00000134899 ERCC5 seminal vesicle glandular cells Medium Supported P28715 +ENSG00000134899 ERCC5 testis cells in seminiferous ducts Medium Supported P28715 +ENSG00000134899 ERCC5 testis Leydig cells Medium Supported P28715 +ENSG00000134940 ACRV1 testis elongated or late spermatids High Enhanced P26436 +ENSG00000134940 ACRV1 testis round or early spermatids High Enhanced P26436 +ENSG00000134970 TMED7 epididymis glandular cells High Supported Q9Y3B3 +ENSG00000134970 TMED7 prostate glandular cells Medium Supported Q9Y3B3 +ENSG00000134970 TMED7 seminal vesicle glandular cells Medium Supported Q9Y3B3 +ENSG00000134970 TMED7 testis cells in seminiferous ducts Low Supported Q9Y3B3 +ENSG00000134970 TMED7 testis Leydig cells Low Supported Q9Y3B3 +ENSG00000134982 APC epididymis glandular cells Medium Supported P25054 +ENSG00000134982 APC prostate glandular cells Low Supported P25054 +ENSG00000134982 APC seminal vesicle glandular cells Medium Supported P25054 +ENSG00000134982 APC testis cells in seminiferous ducts Medium Supported P25054 +ENSG00000134982 APC testis Leydig cells Low Supported P25054 +ENSG00000134987 WDR36 epididymis glandular cells Medium Supported Q8NI36 +ENSG00000134987 WDR36 prostate glandular cells Medium Supported Q8NI36 +ENSG00000134987 WDR36 seminal vesicle glandular cells Medium Supported Q8NI36 +ENSG00000134987 WDR36 testis cells in seminiferous ducts Medium Supported Q8NI36 +ENSG00000134987 WDR36 testis Leydig cells Medium Supported Q8NI36 +ENSG00000135018 UBQLN1 epididymis glandular cells Medium Supported Q9UMX0 +ENSG00000135018 UBQLN1 prostate glandular cells High Supported Q9UMX0 +ENSG00000135018 UBQLN1 seminal vesicle glandular cells Medium Supported Q9UMX0 +ENSG00000135018 UBQLN1 testis cells in seminiferous ducts High Supported Q9UMX0 +ENSG00000135018 UBQLN1 testis Leydig cells Medium Supported Q9UMX0 +ENSG00000135045 C9orf40 prostate glandular cells Low Enhanced Q8IXQ3 +ENSG00000135045 C9orf40 testis cells in seminiferous ducts High Enhanced Q8IXQ3 +ENSG00000135045 C9orf40 testis Leydig cells Low Enhanced Q8IXQ3 +ENSG00000135046 ANXA1 epididymis glandular cells Medium Enhanced P04083 +ENSG00000135046 ANXA1 prostate glandular cells High Enhanced P04083 +ENSG00000135046 ANXA1 seminal vesicle glandular cells Medium Enhanced P04083 +ENSG00000135047 CTSL epididymis glandular cells Low Enhanced P07711 +ENSG00000135047 CTSL prostate glandular cells Low Enhanced P07711 +ENSG00000135047 CTSL seminal vesicle glandular cells Low Enhanced P07711 +ENSG00000135052 GOLM1 epididymis glandular cells Medium Enhanced Q8NBJ4 +ENSG00000135052 GOLM1 prostate glandular cells High Enhanced Q8NBJ4 +ENSG00000135052 GOLM1 seminal vesicle glandular cells Low Enhanced Q8NBJ4 +ENSG00000135052 GOLM1 testis cells in seminiferous ducts Low Enhanced Q8NBJ4 +ENSG00000135052 GOLM1 testis Leydig cells Medium Enhanced Q8NBJ4 +ENSG00000135069 PSAT1 epididymis glandular cells Medium Enhanced Q9Y617 +ENSG00000135069 PSAT1 testis cells in seminiferous ducts Low Enhanced Q9Y617 +ENSG00000135119 RNFT2 epididymis glandular cells Low Enhanced Q96EX2 +ENSG00000135119 RNFT2 testis Leydig cells Low Enhanced Q96EX2 +ENSG00000135124 P2RX4 epididymis glandular cells Medium Enhanced Q99571 +ENSG00000135124 P2RX4 prostate glandular cells Medium Enhanced Q99571 +ENSG00000135124 P2RX4 seminal vesicle glandular cells Medium Enhanced Q99571 +ENSG00000135124 P2RX4 testis cells in seminiferous ducts Medium Enhanced Q99571 +ENSG00000135124 P2RX4 testis Leydig cells Medium Enhanced Q99571 +ENSG00000135127 BICDL1 epididymis glandular cells High Enhanced Q6ZP65 +ENSG00000135127 BICDL1 testis cells in seminiferous ducts Medium Enhanced Q6ZP65 +ENSG00000135148 TRAFD1 testis cells in seminiferous ducts High Enhanced O14545 +ENSG00000135164 DMTF1 epididymis glandular cells High Supported Q9Y222 +ENSG00000135164 DMTF1 prostate glandular cells Medium Supported Q9Y222 +ENSG00000135164 DMTF1 seminal vesicle glandular cells High Supported Q9Y222 +ENSG00000135164 DMTF1 testis cells in seminiferous ducts High Supported Q9Y222 +ENSG00000135164 DMTF1 testis Leydig cells Medium Supported Q9Y222 +ENSG00000135218 CD36 epididymis glandular cells Low Enhanced P16671 +ENSG00000135299 ANKRD6 epididymis glandular cells Medium Enhanced Q9Y2G4 +ENSG00000135299 ANKRD6 prostate glandular cells Low Enhanced Q9Y2G4 +ENSG00000135299 ANKRD6 seminal vesicle glandular cells Low Enhanced Q9Y2G4 +ENSG00000135299 ANKRD6 testis cells in seminiferous ducts Medium Enhanced Q9Y2G4 +ENSG00000135299 ANKRD6 testis Leydig cells Medium Enhanced Q9Y2G4 +ENSG00000135315 CEP162 epididymis glandular cells Medium Supported Q5TB80 +ENSG00000135315 CEP162 prostate glandular cells Medium Supported Q5TB80 +ENSG00000135315 CEP162 seminal vesicle glandular cells Medium Supported Q5TB80 +ENSG00000135315 CEP162 testis cells in seminiferous ducts Medium Supported Q5TB80 +ENSG00000135315 CEP162 testis Leydig cells Medium Supported Q5TB80 +ENSG00000135316 SYNCRIP epididymis glandular cells Medium Enhanced O60506 +ENSG00000135316 SYNCRIP prostate glandular cells Low Enhanced O60506 +ENSG00000135316 SYNCRIP seminal vesicle glandular cells Medium Enhanced O60506 +ENSG00000135316 SYNCRIP testis cells in seminiferous ducts Medium Enhanced O60506 +ENSG00000135316 SYNCRIP testis Leydig cells Low Enhanced O60506 +ENSG00000135336 ORC3 epididymis glandular cells Medium Enhanced Q9UBD5 +ENSG00000135336 ORC3 prostate glandular cells Medium Enhanced Q9UBD5 +ENSG00000135336 ORC3 seminal vesicle glandular cells Medium Enhanced Q9UBD5 +ENSG00000135336 ORC3 testis cells in seminiferous ducts Medium Enhanced Q9UBD5 +ENSG00000135336 ORC3 testis Leydig cells Medium Enhanced Q9UBD5 +ENSG00000135338 LCA5 prostate glandular cells Medium Supported Q86VQ0 +ENSG00000135338 LCA5 seminal vesicle glandular cells Low Supported Q86VQ0 +ENSG00000135338 LCA5 testis cells in seminiferous ducts Medium Supported Q86VQ0 +ENSG00000135338 LCA5 testis Leydig cells Medium Supported Q86VQ0 +ENSG00000135372 NAT10 epididymis glandular cells Medium Enhanced Q9H0A0 +ENSG00000135372 NAT10 prostate glandular cells Medium Enhanced Q9H0A0 +ENSG00000135372 NAT10 testis cells in seminiferous ducts Medium Enhanced Q9H0A0 +ENSG00000135372 NAT10 testis Leydig cells Low Enhanced Q9H0A0 +ENSG00000135373 EHF epididymis glandular cells Low Enhanced Q9NZC4 +ENSG00000135373 EHF seminal vesicle glandular cells Low Enhanced Q9NZC4 +ENSG00000135404 CD63 epididymis glandular cells Medium Supported P08962 +ENSG00000135404 CD63 prostate glandular cells Medium Supported P08962 +ENSG00000135404 CD63 seminal vesicle glandular cells Medium Supported P08962 +ENSG00000135404 CD63 testis cells in seminiferous ducts Low Supported P08962 +ENSG00000135404 CD63 testis Leydig cells Medium Supported P08962 +ENSG00000135414 GDF11 epididymis glandular cells Medium Enhanced O95390 +ENSG00000135414 GDF11 prostate glandular cells Medium Enhanced O95390 +ENSG00000135414 GDF11 testis Leydig cells High Enhanced O95390 +ENSG00000135446 CDK4 epididymis glandular cells Low Enhanced P11802 +ENSG00000135446 CDK4 testis Leydig cells Low Enhanced P11802 +ENSG00000135480 KRT7 epididymis glandular cells Medium Enhanced P08729 +ENSG00000135480 KRT7 prostate glandular cells Medium Enhanced P08729 +ENSG00000135480 KRT7 seminal vesicle glandular cells High Enhanced P08729 +ENSG00000135486 HNRNPA1 epididymis glandular cells High Supported P09651 +ENSG00000135486 HNRNPA1 prostate glandular cells High Supported P09651 +ENSG00000135486 HNRNPA1 seminal vesicle glandular cells High Supported P09651 +ENSG00000135486 HNRNPA1 testis cells in seminiferous ducts High Supported P09651 +ENSG00000135486 HNRNPA1 testis Leydig cells High Supported P09651 +ENSG00000135506 OS9 epididymis glandular cells High Supported Q13438 +ENSG00000135506 OS9 prostate glandular cells Medium Supported Q13438 +ENSG00000135506 OS9 seminal vesicle glandular cells Medium Supported Q13438 +ENSG00000135506 OS9 testis cells in seminiferous ducts High Supported Q13438 +ENSG00000135506 OS9 testis Leydig cells Medium Supported Q13438 +ENSG00000135525 MAP7 epididymis glandular cells High Enhanced Q14244 +ENSG00000135525 MAP7 prostate glandular cells High Enhanced Q14244 +ENSG00000135525 MAP7 seminal vesicle glandular cells High Enhanced Q14244 +ENSG00000135525 MAP7 testis cells in seminiferous ducts Medium Enhanced Q14244 +ENSG00000135631 RAB11FIP5 epididymis glandular cells Medium Enhanced Q9BXF6 +ENSG00000135631 RAB11FIP5 testis elongated or late spermatids High Enhanced Q9BXF6 +ENSG00000135631 RAB11FIP5 testis Leydig cells Low Enhanced Q9BXF6 +ENSG00000135631 RAB11FIP5 testis pachytene spermatocytes Medium Enhanced Q9BXF6 +ENSG00000135631 RAB11FIP5 testis preleptotene spermatocytes Low Enhanced Q9BXF6 +ENSG00000135631 RAB11FIP5 testis round or early spermatids High Enhanced Q9BXF6 +ENSG00000135636 DYSF testis cells in seminiferous ducts Medium Enhanced O75923 +ENSG00000135636 DYSF testis Leydig cells Low Enhanced O75923 +ENSG00000135677 GNS epididymis glandular cells Medium Enhanced P15586 +ENSG00000135677 GNS prostate glandular cells Medium Enhanced P15586 +ENSG00000135677 GNS seminal vesicle glandular cells Medium Enhanced P15586 +ENSG00000135677 GNS testis cells in seminiferous ducts Medium Enhanced P15586 +ENSG00000135677 GNS testis Leydig cells High Enhanced P15586 +ENSG00000135679 MDM2 epididymis glandular cells High Supported Q00987 +ENSG00000135679 MDM2 prostate glandular cells High Supported Q00987 +ENSG00000135679 MDM2 seminal vesicle glandular cells High Supported Q00987 +ENSG00000135679 MDM2 testis cells in seminiferous ducts High Supported Q00987 +ENSG00000135679 MDM2 testis Leydig cells High Supported Q00987 +ENSG00000135736 CCDC102A epididymis glandular cells Low Supported Q96A19 +ENSG00000135736 CCDC102A prostate glandular cells Medium Supported Q96A19 +ENSG00000135736 CCDC102A seminal vesicle glandular cells Low Supported Q96A19 +ENSG00000135736 CCDC102A testis cells in seminiferous ducts Low Supported Q96A19 +ENSG00000135736 CCDC102A testis Leydig cells Medium Supported Q96A19 +ENSG00000135744 AGT prostate glandular cells Medium Supported P01019 +ENSG00000135744 AGT seminal vesicle glandular cells Low Supported P01019 +ENSG00000135744 AGT testis cells in seminiferous ducts Medium Supported P01019 +ENSG00000135744 AGT testis Leydig cells Medium Supported P01019 +ENSG00000135773 CAPN9 seminal vesicle glandular cells Low Enhanced O14815 +ENSG00000135824 RGS8 testis cells in seminiferous ducts Low Supported P57771 +ENSG00000135829 DHX9 epididymis glandular cells High Supported Q08211 +ENSG00000135829 DHX9 prostate glandular cells Medium Supported Q08211 +ENSG00000135829 DHX9 seminal vesicle glandular cells Medium Supported Q08211 +ENSG00000135829 DHX9 testis cells in seminiferous ducts High Supported Q08211 +ENSG00000135829 DHX9 testis Leydig cells Medium Supported Q08211 +ENSG00000135837 CEP350 epididymis glandular cells High Enhanced Q5VT06 +ENSG00000135837 CEP350 prostate glandular cells Medium Enhanced Q5VT06 +ENSG00000135837 CEP350 seminal vesicle glandular cells Medium Enhanced Q5VT06 +ENSG00000135837 CEP350 testis cells in seminiferous ducts High Enhanced Q5VT06 +ENSG00000135837 CEP350 testis Leydig cells High Enhanced Q5VT06 +ENSG00000135862 LAMC1 prostate glandular cells Low Enhanced P11047 +ENSG00000135862 LAMC1 testis cells in seminiferous ducts Low Enhanced P11047 +ENSG00000135862 LAMC1 testis Leydig cells Low Enhanced P11047 +ENSG00000135905 DOCK10 testis Leydig cells Low Enhanced Q96BY6 +ENSG00000135914 HTR2B epididymis glandular cells Medium Enhanced P41595 +ENSG00000135914 HTR2B prostate glandular cells Low Enhanced P41595 +ENSG00000135914 HTR2B seminal vesicle glandular cells Low Enhanced P41595 +ENSG00000135929 CYP27A1 epididymis glandular cells Medium Enhanced Q02318 +ENSG00000135929 CYP27A1 prostate glandular cells Low Enhanced Q02318 +ENSG00000135929 CYP27A1 seminal vesicle glandular cells High Enhanced Q02318 +ENSG00000135929 CYP27A1 testis cells in seminiferous ducts Medium Enhanced Q02318 +ENSG00000135929 CYP27A1 testis Leydig cells Medium Enhanced Q02318 +ENSG00000135932 CAB39 epididymis glandular cells High Supported Q9Y376 +ENSG00000135932 CAB39 prostate glandular cells Medium Supported Q9Y376 +ENSG00000135932 CAB39 seminal vesicle glandular cells Medium Supported Q9Y376 +ENSG00000135932 CAB39 testis cells in seminiferous ducts High Supported Q9Y376 +ENSG00000135932 CAB39 testis Leydig cells Medium Supported Q9Y376 +ENSG00000135940 COX5B epididymis glandular cells High Supported P10606 +ENSG00000135940 COX5B prostate glandular cells High Supported P10606 +ENSG00000135940 COX5B seminal vesicle glandular cells High Supported P10606 +ENSG00000135940 COX5B testis cells in seminiferous ducts High Supported P10606 +ENSG00000135940 COX5B testis Leydig cells High Supported P10606 +ENSG00000135968 GCC2 epididymis glandular cells High Enhanced Q8IWJ2 +ENSG00000135968 GCC2 prostate glandular cells Medium Enhanced Q8IWJ2 +ENSG00000135968 GCC2 seminal vesicle glandular cells Medium Enhanced Q8IWJ2 +ENSG00000135968 GCC2 testis cells in seminiferous ducts Medium Enhanced Q8IWJ2 +ENSG00000135968 GCC2 testis Leydig cells Medium Enhanced Q8IWJ2 +ENSG00000135972 MRPS9 epididymis glandular cells High Enhanced P82933 +ENSG00000135972 MRPS9 prostate glandular cells High Enhanced P82933 +ENSG00000135972 MRPS9 seminal vesicle glandular cells High Enhanced P82933 +ENSG00000135972 MRPS9 testis cells in seminiferous ducts High Enhanced P82933 +ENSG00000135972 MRPS9 testis Leydig cells High Enhanced P82933 +ENSG00000136026 CKAP4 epididymis glandular cells Medium Enhanced Q07065 +ENSG00000136026 CKAP4 prostate glandular cells Medium Enhanced Q07065 +ENSG00000136026 CKAP4 seminal vesicle glandular cells Medium Enhanced Q07065 +ENSG00000136026 CKAP4 testis cells in seminiferous ducts Low Enhanced Q07065 +ENSG00000136026 CKAP4 testis Leydig cells Medium Enhanced Q07065 +ENSG00000136068 FLNB epididymis glandular cells High Enhanced O75369 +ENSG00000136068 FLNB prostate glandular cells High Enhanced O75369 +ENSG00000136068 FLNB seminal vesicle glandular cells High Enhanced O75369 +ENSG00000136068 FLNB testis cells in seminiferous ducts High Enhanced O75369 +ENSG00000136068 FLNB testis Leydig cells Medium Enhanced O75369 +ENSG00000136098 NEK3 epididymis glandular cells Medium Enhanced P51956 +ENSG00000136098 NEK3 prostate glandular cells Medium Enhanced P51956 +ENSG00000136098 NEK3 seminal vesicle glandular cells Low Enhanced P51956 +ENSG00000136098 NEK3 testis cells in seminiferous ducts Low Enhanced P51956 +ENSG00000136098 NEK3 testis Leydig cells Low Enhanced P51956 +ENSG00000136108 CKAP2 epididymis glandular cells Low Enhanced Q8WWK9 +ENSG00000136108 CKAP2 testis pachytene spermatocytes High Enhanced Q8WWK9 +ENSG00000136108 CKAP2 testis preleptotene spermatocytes Low Enhanced Q8WWK9 +ENSG00000136108 CKAP2 testis round or early spermatids Medium Enhanced Q8WWK9 +ENSG00000136143 SUCLA2 epididymis glandular cells Medium Enhanced Q9P2R7 +ENSG00000136143 SUCLA2 prostate glandular cells Medium Enhanced Q9P2R7 +ENSG00000136143 SUCLA2 seminal vesicle glandular cells High Enhanced Q9P2R7 +ENSG00000136143 SUCLA2 testis cells in seminiferous ducts Medium Enhanced Q9P2R7 +ENSG00000136143 SUCLA2 testis Leydig cells Medium Enhanced Q9P2R7 +ENSG00000136167 LCP1 epididymis glandular cells High Enhanced P13796 +ENSG00000136193 SCRN1 epididymis glandular cells Low Enhanced Q12765 +ENSG00000136193 SCRN1 prostate glandular cells Low Enhanced Q12765 +ENSG00000136193 SCRN1 seminal vesicle glandular cells Low Enhanced Q12765 +ENSG00000136193 SCRN1 testis cells in seminiferous ducts Medium Enhanced Q12765 +ENSG00000136206 SPDYE1 testis cells in seminiferous ducts Medium Supported Q8NFV5 +ENSG00000136206 SPDYE1 testis elongated or late spermatids High Supported Q8NFV5 +ENSG00000136206 SPDYE1 testis round or early spermatids Medium Supported Q8NFV5 +ENSG00000136279 DBNL epididymis glandular cells Medium Enhanced Q9UJU6 +ENSG00000136279 DBNL prostate glandular cells Low Enhanced Q9UJU6 +ENSG00000136279 DBNL seminal vesicle glandular cells Low Enhanced Q9UJU6 +ENSG00000136279 DBNL testis cells in seminiferous ducts Medium Enhanced Q9UJU6 +ENSG00000136279 DBNL testis Leydig cells Low Enhanced Q9UJU6 +ENSG00000136280 CCM2 epididymis glandular cells Medium Enhanced Q9BSQ5 +ENSG00000136280 CCM2 prostate glandular cells Low Enhanced Q9BSQ5 +ENSG00000136280 CCM2 seminal vesicle glandular cells Low Enhanced Q9BSQ5 +ENSG00000136280 CCM2 testis cells in seminiferous ducts Low Enhanced Q9BSQ5 +ENSG00000136280 CCM2 testis Leydig cells Low Enhanced Q9BSQ5 +ENSG00000136436 CALCOCO2 epididymis glandular cells Medium Enhanced Q13137 +ENSG00000136436 CALCOCO2 prostate glandular cells Low Enhanced Q13137 +ENSG00000136436 CALCOCO2 seminal vesicle glandular cells Low Enhanced Q13137 +ENSG00000136436 CALCOCO2 testis cells in seminiferous ducts Medium Enhanced Q13137 +ENSG00000136436 CALCOCO2 testis Leydig cells Medium Enhanced Q13137 +ENSG00000136448 NMT1 epididymis glandular cells Medium Enhanced P30419 +ENSG00000136448 NMT1 prostate glandular cells Medium Enhanced P30419 +ENSG00000136448 NMT1 seminal vesicle glandular cells Medium Enhanced P30419 +ENSG00000136448 NMT1 testis cells in seminiferous ducts Medium Enhanced P30419 +ENSG00000136448 NMT1 testis Leydig cells Low Enhanced P30419 +ENSG00000136449 MYCBPAP testis cells in seminiferous ducts Medium Enhanced Q8TBZ2 +ENSG00000136450 SRSF1 epididymis glandular cells High Supported Q07955 +ENSG00000136450 SRSF1 prostate glandular cells Medium Supported Q07955 +ENSG00000136450 SRSF1 seminal vesicle glandular cells High Supported Q07955 +ENSG00000136450 SRSF1 testis cells in seminiferous ducts High Supported Q07955 +ENSG00000136450 SRSF1 testis Leydig cells High Supported Q07955 +ENSG00000136463 TACO1 epididymis glandular cells Medium Enhanced Q9BSH4 +ENSG00000136463 TACO1 prostate glandular cells Medium Enhanced Q9BSH4 +ENSG00000136463 TACO1 seminal vesicle glandular cells Medium Enhanced Q9BSH4 +ENSG00000136463 TACO1 testis cells in seminiferous ducts Medium Enhanced Q9BSH4 +ENSG00000136463 TACO1 testis Leydig cells Medium Enhanced Q9BSH4 +ENSG00000136485 DCAF7 epididymis glandular cells Medium Enhanced P61962 +ENSG00000136485 DCAF7 prostate glandular cells Medium Enhanced P61962 +ENSG00000136485 DCAF7 seminal vesicle glandular cells Low Enhanced P61962 +ENSG00000136485 DCAF7 testis cells in seminiferous ducts Low Enhanced P61962 +ENSG00000136485 DCAF7 testis Leydig cells Medium Enhanced P61962 +ENSG00000136518 ACTL6A epididymis glandular cells High Supported O96019 +ENSG00000136518 ACTL6A prostate glandular cells High Supported O96019 +ENSG00000136518 ACTL6A seminal vesicle glandular cells Medium Supported O96019 +ENSG00000136518 ACTL6A testis cells in seminiferous ducts High Supported O96019 +ENSG00000136518 ACTL6A testis Leydig cells High Supported O96019 +ENSG00000136521 NDUFB5 epididymis glandular cells High Enhanced O43674 +ENSG00000136521 NDUFB5 prostate glandular cells High Enhanced O43674 +ENSG00000136521 NDUFB5 seminal vesicle glandular cells High Enhanced O43674 +ENSG00000136521 NDUFB5 testis cells in seminiferous ducts Low Enhanced O43674 +ENSG00000136521 NDUFB5 testis Leydig cells Medium Enhanced O43674 +ENSG00000136527 TRA2B epididymis glandular cells High Supported P62995 +ENSG00000136527 TRA2B prostate glandular cells High Supported P62995 +ENSG00000136527 TRA2B seminal vesicle glandular cells High Supported P62995 +ENSG00000136527 TRA2B testis cells in seminiferous ducts High Supported P62995 +ENSG00000136527 TRA2B testis Leydig cells High Supported P62995 +ENSG00000136536 MARCH7 epididymis glandular cells Medium Enhanced Q9H992 +ENSG00000136536 MARCH7 prostate glandular cells Medium Enhanced Q9H992 +ENSG00000136536 MARCH7 seminal vesicle glandular cells Medium Enhanced Q9H992 +ENSG00000136536 MARCH7 testis cells in seminiferous ducts Medium Enhanced Q9H992 +ENSG00000136536 MARCH7 testis Leydig cells Medium Enhanced Q9H992 +ENSG00000136628 EPRS epididymis glandular cells Medium Enhanced P07814 +ENSG00000136628 EPRS prostate glandular cells Low Enhanced P07814 +ENSG00000136628 EPRS seminal vesicle glandular cells Medium Enhanced P07814 +ENSG00000136628 EPRS testis cells in seminiferous ducts Low Enhanced P07814 +ENSG00000136709 WDR33 epididymis glandular cells High Supported Q9C0J8 +ENSG00000136709 WDR33 prostate glandular cells Medium Supported Q9C0J8 +ENSG00000136709 WDR33 seminal vesicle glandular cells Medium Supported Q9C0J8 +ENSG00000136709 WDR33 testis cells in seminiferous ducts Medium Supported Q9C0J8 +ENSG00000136709 WDR33 testis Leydig cells Medium Supported Q9C0J8 +ENSG00000136717 BIN1 epididymis glandular cells Medium Enhanced O00499 +ENSG00000136717 BIN1 prostate glandular cells Medium Enhanced O00499 +ENSG00000136717 BIN1 seminal vesicle glandular cells Medium Enhanced O00499 +ENSG00000136717 BIN1 testis cells in seminiferous ducts Low Enhanced O00499 +ENSG00000136717 BIN1 testis Leydig cells Medium Enhanced O00499 +ENSG00000136731 UGGT1 epididymis glandular cells High Enhanced Q9NYU2 +ENSG00000136731 UGGT1 prostate glandular cells Medium Enhanced Q9NYU2 +ENSG00000136731 UGGT1 seminal vesicle glandular cells Medium Enhanced Q9NYU2 +ENSG00000136731 UGGT1 testis cells in seminiferous ducts Medium Enhanced Q9NYU2 +ENSG00000136731 UGGT1 testis Leydig cells Medium Enhanced Q9NYU2 +ENSG00000136732 GYPC epididymis glandular cells Low Enhanced P04921 +ENSG00000136732 GYPC seminal vesicle glandular cells Low Enhanced P04921 +ENSG00000136732 GYPC testis cells in seminiferous ducts Medium Enhanced P04921 +ENSG00000136732 GYPC testis Leydig cells Medium Enhanced P04921 +ENSG00000136738 STAM epididymis glandular cells Medium Supported Q92783 +ENSG00000136738 STAM prostate glandular cells Low Supported Q92783 +ENSG00000136738 STAM seminal vesicle glandular cells Medium Supported Q92783 +ENSG00000136738 STAM testis cells in seminiferous ducts Medium Supported Q92783 +ENSG00000136738 STAM testis Leydig cells Medium Supported Q92783 +ENSG00000136807 CDK9 epididymis glandular cells High Supported P50750 +ENSG00000136807 CDK9 prostate glandular cells High Supported P50750 +ENSG00000136807 CDK9 seminal vesicle glandular cells High Supported P50750 +ENSG00000136807 CDK9 testis cells in seminiferous ducts High Supported P50750 +ENSG00000136807 CDK9 testis Leydig cells High Supported P50750 +ENSG00000136810 TXN epididymis glandular cells Low Enhanced P10599 +ENSG00000136810 TXN prostate glandular cells Medium Enhanced P10599 +ENSG00000136810 TXN seminal vesicle glandular cells Medium Enhanced P10599 +ENSG00000136810 TXN testis cells in seminiferous ducts Low Enhanced P10599 +ENSG00000136810 TXN testis Leydig cells High Enhanced P10599 +ENSG00000136811 ODF2 testis elongated or late spermatids High Enhanced Q5BJF6 +ENSG00000136811 ODF2 testis pachytene spermatocytes Low Enhanced Q5BJF6 +ENSG00000136811 ODF2 testis preleptotene spermatocytes Low Enhanced Q5BJF6 +ENSG00000136811 ODF2 testis round or early spermatids Medium Enhanced Q5BJF6 +ENSG00000136811 ODF2 testis spermatogonia Low Enhanced Q5BJF6 +ENSG00000136819 C9orf78 epididymis glandular cells Medium Enhanced Q9NZ63 +ENSG00000136819 C9orf78 testis cells in seminiferous ducts High Enhanced Q9NZ63 +ENSG00000136819 C9orf78 testis Leydig cells Medium Enhanced Q9NZ63 +ENSG00000136826 KLF4 testis cells in seminiferous ducts Medium Enhanced O43474 +ENSG00000136826 KLF4 testis Leydig cells Low Enhanced O43474 +ENSG00000136875 PRPF4 epididymis glandular cells Medium Enhanced O43172 +ENSG00000136875 PRPF4 prostate glandular cells Medium Enhanced O43172 +ENSG00000136875 PRPF4 seminal vesicle glandular cells Medium Enhanced O43172 +ENSG00000136875 PRPF4 testis cells in seminiferous ducts High Enhanced O43172 +ENSG00000136875 PRPF4 testis Leydig cells High Enhanced O43172 +ENSG00000136888 ATP6V1G1 epididymis glandular cells High Supported O75348 +ENSG00000136888 ATP6V1G1 prostate glandular cells Medium Supported O75348 +ENSG00000136888 ATP6V1G1 seminal vesicle glandular cells High Supported O75348 +ENSG00000136888 ATP6V1G1 testis cells in seminiferous ducts Medium Supported O75348 +ENSG00000136888 ATP6V1G1 testis Leydig cells High Supported O75348 +ENSG00000136929 HEMGN testis elongated or late spermatids High Enhanced Q9BXL5 +ENSG00000136929 HEMGN testis pachytene spermatocytes Low Enhanced Q9BXL5 +ENSG00000136929 HEMGN testis round or early spermatids High Enhanced Q9BXL5 +ENSG00000136930 PSMB7 epididymis glandular cells High Enhanced Q99436 +ENSG00000136930 PSMB7 prostate glandular cells High Enhanced Q99436 +ENSG00000136930 PSMB7 seminal vesicle glandular cells High Enhanced Q99436 +ENSG00000136930 PSMB7 testis cells in seminiferous ducts High Enhanced Q99436 +ENSG00000136930 PSMB7 testis Leydig cells High Enhanced Q99436 +ENSG00000136933 RABEPK epididymis glandular cells Medium Enhanced Q7Z6M1 +ENSG00000136933 RABEPK prostate glandular cells High Enhanced Q7Z6M1 +ENSG00000136933 RABEPK seminal vesicle glandular cells Medium Enhanced Q7Z6M1 +ENSG00000136933 RABEPK testis cells in seminiferous ducts Medium Enhanced Q7Z6M1 +ENSG00000136933 RABEPK testis Leydig cells Medium Enhanced Q7Z6M1 +ENSG00000136935 GOLGA1 epididymis glandular cells High Enhanced Q92805 +ENSG00000136935 GOLGA1 prostate glandular cells Medium Enhanced Q92805 +ENSG00000136935 GOLGA1 seminal vesicle glandular cells Medium Enhanced Q92805 +ENSG00000136935 GOLGA1 testis cells in seminiferous ducts High Enhanced Q92805 +ENSG00000136935 GOLGA1 testis Leydig cells Medium Enhanced Q92805 +ENSG00000136936 XPA epididymis glandular cells High Supported P23025 +ENSG00000136936 XPA prostate glandular cells High Supported P23025 +ENSG00000136936 XPA seminal vesicle glandular cells Medium Supported P23025 +ENSG00000136936 XPA testis cells in seminiferous ducts Medium Supported P23025 +ENSG00000136936 XPA testis Leydig cells Low Supported P23025 +ENSG00000136937 NCBP1 epididymis glandular cells Medium Enhanced Q09161 +ENSG00000136937 NCBP1 prostate glandular cells Medium Enhanced Q09161 +ENSG00000136937 NCBP1 seminal vesicle glandular cells High Enhanced Q09161 +ENSG00000136937 NCBP1 testis cells in seminiferous ducts High Enhanced Q09161 +ENSG00000136937 NCBP1 testis Leydig cells Medium Enhanced Q09161 +ENSG00000136938 ANP32B epididymis glandular cells High Supported Q92688 +ENSG00000136938 ANP32B prostate glandular cells High Supported Q92688 +ENSG00000136938 ANP32B seminal vesicle glandular cells High Supported Q92688 +ENSG00000136938 ANP32B testis cells in seminiferous ducts Medium Supported Q92688 +ENSG00000136938 ANP32B testis Leydig cells High Supported Q92688 +ENSG00000136986 DERL1 epididymis glandular cells Medium Enhanced Q9BUN8 +ENSG00000136986 DERL1 prostate glandular cells Medium Enhanced Q9BUN8 +ENSG00000136986 DERL1 seminal vesicle glandular cells High Enhanced Q9BUN8 +ENSG00000136986 DERL1 testis cells in seminiferous ducts Medium Enhanced Q9BUN8 +ENSG00000136986 DERL1 testis Leydig cells High Enhanced Q9BUN8 +ENSG00000136997 MYC epididymis glandular cells Medium Supported P01106 +ENSG00000136997 MYC prostate glandular cells Medium Supported P01106 +ENSG00000136997 MYC seminal vesicle glandular cells Medium Supported P01106 +ENSG00000136997 MYC testis cells in seminiferous ducts High Supported P01106 +ENSG00000136997 MYC testis Leydig cells Medium Supported P01106 +ENSG00000137033 IL33 prostate glandular cells Low Supported O95760 +ENSG00000137033 IL33 testis Leydig cells Low Supported O95760 +ENSG00000137054 POLR1E epididymis glandular cells Medium Supported Q9GZS1 +ENSG00000137054 POLR1E prostate glandular cells Medium Supported Q9GZS1 +ENSG00000137054 POLR1E seminal vesicle glandular cells Medium Supported Q9GZS1 +ENSG00000137054 POLR1E testis cells in seminiferous ducts High Supported Q9GZS1 +ENSG00000137054 POLR1E testis Leydig cells Medium Supported Q9GZS1 +ENSG00000137070 IL11RA epididymis glandular cells Low Supported Q14626 +ENSG00000137070 IL11RA prostate glandular cells Medium Supported Q14626 +ENSG00000137070 IL11RA seminal vesicle glandular cells High Supported Q14626 +ENSG00000137070 IL11RA testis cells in seminiferous ducts Medium Supported Q14626 +ENSG00000137070 IL11RA testis Leydig cells Medium Supported Q14626 +ENSG00000137074 APTX epididymis glandular cells High Supported Q7Z2E3 +ENSG00000137074 APTX prostate glandular cells Medium Supported Q7Z2E3 +ENSG00000137074 APTX seminal vesicle glandular cells Medium Supported Q7Z2E3 +ENSG00000137074 APTX testis cells in seminiferous ducts High Supported Q7Z2E3 +ENSG00000137074 APTX testis Leydig cells High Supported Q7Z2E3 +ENSG00000137076 TLN1 epididymis glandular cells High Supported Q9Y490 +ENSG00000137076 TLN1 prostate glandular cells Low Supported Q9Y490 +ENSG00000137076 TLN1 seminal vesicle glandular cells Medium Supported Q9Y490 +ENSG00000137076 TLN1 testis cells in seminiferous ducts High Supported Q9Y490 +ENSG00000137076 TLN1 testis Leydig cells Low Supported Q9Y490 +ENSG00000137090 DMRT1 testis Leydig cells Low Enhanced Q9Y5R6 +ENSG00000137090 DMRT1 testis pachytene spermatocytes Low Enhanced Q9Y5R6 +ENSG00000137090 DMRT1 testis preleptotene spermatocytes High Enhanced Q9Y5R6 +ENSG00000137090 DMRT1 testis round or early spermatids Low Enhanced Q9Y5R6 +ENSG00000137090 DMRT1 testis spermatogonia Medium Enhanced Q9Y5R6 +ENSG00000137098 SPAG8 testis elongated or late spermatids High Enhanced Q99932 +ENSG00000137098 SPAG8 testis Leydig cells Low Enhanced Q99932 +ENSG00000137098 SPAG8 testis pachytene spermatocytes Medium Enhanced Q99932 +ENSG00000137098 SPAG8 testis round or early spermatids Medium Enhanced Q99932 +ENSG00000137133 HINT2 epididymis glandular cells High Enhanced Q9BX68 +ENSG00000137133 HINT2 prostate glandular cells Medium Enhanced Q9BX68 +ENSG00000137133 HINT2 seminal vesicle glandular cells High Enhanced Q9BX68 +ENSG00000137133 HINT2 testis cells in seminiferous ducts Medium Enhanced Q9BX68 +ENSG00000137133 HINT2 testis Leydig cells High Enhanced Q9BX68 +ENSG00000137154 RPS6 epididymis glandular cells Medium Supported P62753 +ENSG00000137154 RPS6 prostate glandular cells Medium Supported P62753 +ENSG00000137154 RPS6 seminal vesicle glandular cells Medium Supported P62753 +ENSG00000137154 RPS6 testis cells in seminiferous ducts High Supported P62753 +ENSG00000137154 RPS6 testis Leydig cells Medium Supported P62753 +ENSG00000137171 KLC4 epididymis glandular cells Medium Enhanced Q9NSK0 +ENSG00000137171 KLC4 prostate glandular cells Medium Enhanced Q9NSK0 +ENSG00000137171 KLC4 seminal vesicle glandular cells Medium Enhanced Q9NSK0 +ENSG00000137171 KLC4 testis cells in seminiferous ducts Medium Enhanced Q9NSK0 +ENSG00000137171 KLC4 testis Leydig cells Medium Enhanced Q9NSK0 +ENSG00000137200 CMTR1 epididymis glandular cells Medium Enhanced Q8N1G2 +ENSG00000137200 CMTR1 prostate glandular cells Low Enhanced Q8N1G2 +ENSG00000137200 CMTR1 seminal vesicle glandular cells Medium Enhanced Q8N1G2 +ENSG00000137200 CMTR1 testis cells in seminiferous ducts High Enhanced Q8N1G2 +ENSG00000137200 CMTR1 testis Leydig cells High Enhanced Q8N1G2 +ENSG00000137203 TFAP2A epididymis glandular cells Medium Enhanced P05549 +ENSG00000137207 YIPF3 epididymis glandular cells High Supported Q9GZM5 +ENSG00000137207 YIPF3 prostate glandular cells High Supported Q9GZM5 +ENSG00000137207 YIPF3 seminal vesicle glandular cells High Supported Q9GZM5 +ENSG00000137207 YIPF3 testis cells in seminiferous ducts High Supported Q9GZM5 +ENSG00000137207 YIPF3 testis Leydig cells High Supported Q9GZM5 +ENSG00000137218 FRS3 epididymis glandular cells Low Enhanced O43559 +ENSG00000137218 FRS3 prostate glandular cells Medium Enhanced O43559 +ENSG00000137218 FRS3 seminal vesicle glandular cells Medium Enhanced O43559 +ENSG00000137221 TJAP1 epididymis glandular cells Medium Supported Q5JTD0 +ENSG00000137221 TJAP1 prostate glandular cells Medium Supported Q5JTD0 +ENSG00000137221 TJAP1 seminal vesicle glandular cells Medium Supported Q5JTD0 +ENSG00000137221 TJAP1 testis cells in seminiferous ducts Medium Supported Q5JTD0 +ENSG00000137221 TJAP1 testis Leydig cells Low Supported Q5JTD0 +ENSG00000137225 CAPN11 testis elongated or late spermatids High Enhanced Q9UMQ6 +ENSG00000137225 CAPN11 testis Leydig cells Low Enhanced Q9UMQ6 +ENSG00000137225 CAPN11 testis pachytene spermatocytes High Enhanced Q9UMQ6 +ENSG00000137225 CAPN11 testis preleptotene spermatocytes Low Enhanced Q9UMQ6 +ENSG00000137225 CAPN11 testis round or early spermatids High Enhanced Q9UMQ6 +ENSG00000137225 CAPN11 testis spermatogonia Low Enhanced Q9UMQ6 +ENSG00000137261 KIAA0319 testis cells in seminiferous ducts Medium Enhanced Q5VV43 +ENSG00000137267 TUBB2A epididymis glandular cells Low Supported Q13885 +ENSG00000137267 TUBB2A testis cells in seminiferous ducts Low Supported Q13885 +ENSG00000137269 LRRC1 epididymis glandular cells Medium Enhanced Q9BTT6 +ENSG00000137269 LRRC1 prostate glandular cells High Enhanced Q9BTT6 +ENSG00000137269 LRRC1 seminal vesicle glandular cells Medium Enhanced Q9BTT6 +ENSG00000137269 LRRC1 testis cells in seminiferous ducts Medium Enhanced Q9BTT6 +ENSG00000137274 BPHL epididymis glandular cells Low Enhanced Q86WA6 +ENSG00000137274 BPHL seminal vesicle glandular cells Low Enhanced Q86WA6 +ENSG00000137274 BPHL testis cells in seminiferous ducts Medium Enhanced Q86WA6 +ENSG00000137274 BPHL testis Leydig cells Medium Enhanced Q86WA6 +ENSG00000137275 RIPK1 epididymis glandular cells Medium Enhanced Q13546 +ENSG00000137275 RIPK1 prostate glandular cells Low Enhanced Q13546 +ENSG00000137275 RIPK1 seminal vesicle glandular cells Low Enhanced Q13546 +ENSG00000137275 RIPK1 testis cells in seminiferous ducts Low Enhanced Q13546 +ENSG00000137275 RIPK1 testis Leydig cells Medium Enhanced Q13546 +ENSG00000137285 TUBB2B epididymis glandular cells Low Supported Q9BVA1 +ENSG00000137285 TUBB2B testis cells in seminiferous ducts Low Supported Q9BVA1 +ENSG00000137312 FLOT1 epididymis glandular cells High Enhanced NA +ENSG00000137312 FLOT1 prostate glandular cells High Enhanced NA +ENSG00000137312 FLOT1 seminal vesicle glandular cells High Enhanced NA +ENSG00000137312 FLOT1 testis cells in seminiferous ducts Low Enhanced NA +ENSG00000137312 FLOT1 testis Leydig cells Medium Enhanced NA +ENSG00000137337 MDC1 epididymis glandular cells Medium Enhanced NA +ENSG00000137337 MDC1 prostate glandular cells Medium Enhanced NA +ENSG00000137337 MDC1 seminal vesicle glandular cells Medium Enhanced NA +ENSG00000137337 MDC1 testis elongated or late spermatids High Enhanced NA +ENSG00000137337 MDC1 testis Leydig cells Medium Enhanced NA +ENSG00000137337 MDC1 testis pachytene spermatocytes High Enhanced NA +ENSG00000137337 MDC1 testis preleptotene spermatocytes High Enhanced NA +ENSG00000137337 MDC1 testis round or early spermatids High Enhanced NA +ENSG00000137337 MDC1 testis spermatogonia Low Enhanced NA +ENSG00000137413 TAF8 epididymis glandular cells Medium Supported Q7Z7C8 +ENSG00000137413 TAF8 prostate glandular cells Medium Supported Q7Z7C8 +ENSG00000137413 TAF8 seminal vesicle glandular cells Low Supported Q7Z7C8 +ENSG00000137413 TAF8 testis cells in seminiferous ducts Low Supported Q7Z7C8 +ENSG00000137413 TAF8 testis Leydig cells Low Supported Q7Z7C8 +ENSG00000137463 MGARP testis Leydig cells High Enhanced Q8TDB4 +ENSG00000137497 NUMA1 epididymis glandular cells High Enhanced Q14980 +ENSG00000137497 NUMA1 prostate glandular cells High Enhanced Q14980 +ENSG00000137497 NUMA1 seminal vesicle glandular cells High Enhanced Q14980 +ENSG00000137497 NUMA1 testis cells in seminiferous ducts High Enhanced Q14980 +ENSG00000137497 NUMA1 testis Leydig cells High Enhanced Q14980 +ENSG00000137500 CCDC90B epididymis glandular cells Medium Enhanced Q9GZT6 +ENSG00000137500 CCDC90B prostate glandular cells Medium Enhanced Q9GZT6 +ENSG00000137500 CCDC90B seminal vesicle glandular cells Medium Enhanced Q9GZT6 +ENSG00000137500 CCDC90B testis cells in seminiferous ducts High Enhanced Q9GZT6 +ENSG00000137500 CCDC90B testis Leydig cells Medium Enhanced Q9GZT6 +ENSG00000137513 NARS2 epididymis glandular cells High Supported Q96I59 +ENSG00000137513 NARS2 prostate glandular cells Medium Supported Q96I59 +ENSG00000137513 NARS2 seminal vesicle glandular cells High Supported Q96I59 +ENSG00000137513 NARS2 testis cells in seminiferous ducts Medium Supported Q96I59 +ENSG00000137513 NARS2 testis Leydig cells High Supported Q96I59 +ENSG00000137547 MRPL15 epididymis glandular cells Medium Enhanced Q9P015 +ENSG00000137547 MRPL15 prostate glandular cells Medium Enhanced Q9P015 +ENSG00000137547 MRPL15 seminal vesicle glandular cells Medium Enhanced Q9P015 +ENSG00000137547 MRPL15 testis cells in seminiferous ducts Medium Enhanced Q9P015 +ENSG00000137547 MRPL15 testis Leydig cells Medium Enhanced Q9P015 +ENSG00000137573 SULF1 prostate glandular cells Medium Supported Q8IWU6 +ENSG00000137573 SULF1 testis Leydig cells Low Supported Q8IWU6 +ENSG00000137574 TGS1 epididymis glandular cells High Supported Q96RS0 +ENSG00000137574 TGS1 prostate glandular cells High Supported Q96RS0 +ENSG00000137574 TGS1 seminal vesicle glandular cells High Supported Q96RS0 +ENSG00000137574 TGS1 testis cells in seminiferous ducts High Supported Q96RS0 +ENSG00000137574 TGS1 testis Leydig cells Medium Supported Q96RS0 +ENSG00000137656 BUD13 epididymis glandular cells Medium Enhanced Q9BRD0 +ENSG00000137656 BUD13 prostate glandular cells Medium Enhanced Q9BRD0 +ENSG00000137656 BUD13 seminal vesicle glandular cells Medium Enhanced Q9BRD0 +ENSG00000137656 BUD13 testis cells in seminiferous ducts Medium Enhanced Q9BRD0 +ENSG00000137656 BUD13 testis Leydig cells Medium Enhanced Q9BRD0 +ENSG00000137691 C11orf70 testis cells in seminiferous ducts Low Enhanced Q9BRQ4 +ENSG00000137693 YAP1 epididymis glandular cells Medium Enhanced P46937 +ENSG00000137693 YAP1 prostate glandular cells Medium Enhanced P46937 +ENSG00000137693 YAP1 seminal vesicle glandular cells Medium Enhanced P46937 +ENSG00000137693 YAP1 testis cells in seminiferous ducts Low Enhanced P46937 +ENSG00000137693 YAP1 testis Leydig cells Medium Enhanced P46937 +ENSG00000137699 TRIM29 epididymis glandular cells Low Enhanced Q14134 +ENSG00000137699 TRIM29 prostate glandular cells Medium Enhanced Q14134 +ENSG00000137699 TRIM29 seminal vesicle glandular cells Medium Enhanced Q14134 +ENSG00000137700 SLC37A4 epididymis glandular cells Low Enhanced U3KPU7 +ENSG00000137700 SLC37A4 prostate glandular cells Medium Enhanced U3KPU7 +ENSG00000137700 SLC37A4 seminal vesicle glandular cells Medium Enhanced U3KPU7 +ENSG00000137700 SLC37A4 testis cells in seminiferous ducts Low Enhanced U3KPU7 +ENSG00000137700 SLC37A4 testis Leydig cells Medium Enhanced U3KPU7 +ENSG00000137710 RDX epididymis glandular cells Medium Enhanced P35241 +ENSG00000137710 RDX prostate glandular cells Low Enhanced P35241 +ENSG00000137710 RDX seminal vesicle glandular cells Low Enhanced P35241 +ENSG00000137710 RDX testis cells in seminiferous ducts Medium Enhanced P35241 +ENSG00000137710 RDX testis Leydig cells Medium Enhanced P35241 +ENSG00000137714 FDX1 testis Leydig cells High Enhanced P10109 +ENSG00000137764 MAP2K5 epididymis glandular cells Medium Supported Q13163 +ENSG00000137764 MAP2K5 prostate glandular cells Medium Supported Q13163 +ENSG00000137764 MAP2K5 seminal vesicle glandular cells Low Supported Q13163 +ENSG00000137764 MAP2K5 testis cells in seminiferous ducts Medium Supported Q13163 +ENSG00000137764 MAP2K5 testis Leydig cells Medium Supported Q13163 +ENSG00000137767 SQRDL epididymis glandular cells Low Enhanced Q9Y6N5 +ENSG00000137767 SQRDL prostate glandular cells Medium Enhanced Q9Y6N5 +ENSG00000137767 SQRDL seminal vesicle glandular cells Medium Enhanced Q9Y6N5 +ENSG00000137767 SQRDL testis Leydig cells Medium Enhanced Q9Y6N5 +ENSG00000137776 SLTM epididymis glandular cells High Enhanced Q9NWH9 +ENSG00000137776 SLTM prostate glandular cells High Enhanced Q9NWH9 +ENSG00000137776 SLTM seminal vesicle glandular cells Medium Enhanced Q9NWH9 +ENSG00000137776 SLTM testis cells in seminiferous ducts High Enhanced Q9NWH9 +ENSG00000137776 SLTM testis Leydig cells Medium Enhanced Q9NWH9 +ENSG00000137802 MAPKBP1 epididymis glandular cells Low Enhanced O60336 +ENSG00000137802 MAPKBP1 prostate glandular cells Medium Enhanced O60336 +ENSG00000137802 MAPKBP1 seminal vesicle glandular cells Medium Enhanced O60336 +ENSG00000137802 MAPKBP1 testis cells in seminiferous ducts High Enhanced O60336 +ENSG00000137802 MAPKBP1 testis Leydig cells High Enhanced O60336 +ENSG00000137804 NUSAP1 epididymis glandular cells Low Enhanced Q9BXS6 +ENSG00000137804 NUSAP1 testis cells in seminiferous ducts Medium Enhanced Q9BXS6 +ENSG00000137806 NDUFAF1 prostate glandular cells High Supported Q9Y375 +ENSG00000137806 NDUFAF1 seminal vesicle glandular cells High Supported Q9Y375 +ENSG00000137806 NDUFAF1 testis cells in seminiferous ducts High Supported Q9Y375 +ENSG00000137806 NDUFAF1 testis Leydig cells High Supported Q9Y375 +ENSG00000137812 KNL1 testis pachytene spermatocytes High Supported Q8NG31 +ENSG00000137812 KNL1 testis preleptotene spermatocytes High Supported Q8NG31 +ENSG00000137812 KNL1 testis spermatogonia High Supported Q8NG31 +ENSG00000137824 RMDN3 epididymis glandular cells High Supported Q96TC7 +ENSG00000137824 RMDN3 prostate glandular cells High Supported Q96TC7 +ENSG00000137824 RMDN3 seminal vesicle glandular cells High Supported Q96TC7 +ENSG00000137824 RMDN3 testis cells in seminiferous ducts High Supported Q96TC7 +ENSG00000137824 RMDN3 testis Leydig cells High Supported Q96TC7 +ENSG00000137876 RSL24D1 epididymis glandular cells Medium Enhanced Q9UHA3 +ENSG00000137876 RSL24D1 prostate glandular cells Low Enhanced Q9UHA3 +ENSG00000137876 RSL24D1 testis cells in seminiferous ducts Low Enhanced Q9UHA3 +ENSG00000137876 RSL24D1 testis Leydig cells Medium Enhanced Q9UHA3 +ENSG00000137944 KYAT3 epididymis glandular cells Medium Enhanced Q6YP21 +ENSG00000137944 KYAT3 prostate glandular cells Medium Enhanced Q6YP21 +ENSG00000137944 KYAT3 seminal vesicle glandular cells High Enhanced Q6YP21 +ENSG00000137944 KYAT3 testis cells in seminiferous ducts Medium Enhanced Q6YP21 +ENSG00000137944 KYAT3 testis Leydig cells High Enhanced Q6YP21 +ENSG00000137947 GTF2B epididymis glandular cells High Enhanced Q00403 +ENSG00000137947 GTF2B prostate glandular cells Medium Enhanced Q00403 +ENSG00000137947 GTF2B seminal vesicle glandular cells High Enhanced Q00403 +ENSG00000137947 GTF2B testis cells in seminiferous ducts High Enhanced Q00403 +ENSG00000137947 GTF2B testis Leydig cells High Enhanced Q00403 +ENSG00000137959 IFI44L epididymis glandular cells Low Enhanced Q53G44 +ENSG00000137959 IFI44L prostate glandular cells High Enhanced Q53G44 +ENSG00000137959 IFI44L seminal vesicle glandular cells Low Enhanced Q53G44 +ENSG00000137959 IFI44L testis Leydig cells Medium Enhanced Q53G44 +ENSG00000137975 CLCA2 testis Leydig cells Low Enhanced Q9UQC9 +ENSG00000137992 DBT epididymis glandular cells Medium Enhanced P11182 +ENSG00000137992 DBT prostate glandular cells Medium Enhanced P11182 +ENSG00000137992 DBT seminal vesicle glandular cells Medium Enhanced P11182 +ENSG00000137992 DBT testis cells in seminiferous ducts Low Enhanced P11182 +ENSG00000137992 DBT testis Leydig cells Medium Enhanced P11182 +ENSG00000138029 HADHB epididymis glandular cells Medium Enhanced P55084 +ENSG00000138029 HADHB prostate glandular cells Low Enhanced P55084 +ENSG00000138029 HADHB seminal vesicle glandular cells Medium Enhanced P55084 +ENSG00000138029 HADHB testis cells in seminiferous ducts Medium Enhanced P55084 +ENSG00000138029 HADHB testis Leydig cells High Enhanced P55084 +ENSG00000138035 PNPT1 epididymis glandular cells Medium Supported Q8TCS8 +ENSG00000138035 PNPT1 prostate glandular cells Medium Supported Q8TCS8 +ENSG00000138035 PNPT1 seminal vesicle glandular cells Medium Supported Q8TCS8 +ENSG00000138035 PNPT1 testis cells in seminiferous ducts Medium Supported Q8TCS8 +ENSG00000138035 PNPT1 testis Leydig cells Medium Supported Q8TCS8 +ENSG00000138095 LRPPRC epididymis glandular cells High Enhanced P42704 +ENSG00000138095 LRPPRC prostate glandular cells High Enhanced P42704 +ENSG00000138095 LRPPRC seminal vesicle glandular cells High Enhanced P42704 +ENSG00000138095 LRPPRC testis cells in seminiferous ducts High Enhanced P42704 +ENSG00000138095 LRPPRC testis Leydig cells High Enhanced P42704 +ENSG00000138119 MYOF epididymis glandular cells Medium Enhanced Q9NZM1 +ENSG00000138119 MYOF prostate glandular cells Medium Enhanced Q9NZM1 +ENSG00000138119 MYOF seminal vesicle glandular cells Medium Enhanced Q9NZM1 +ENSG00000138119 MYOF testis Leydig cells Medium Enhanced Q9NZM1 +ENSG00000138160 KIF11 epididymis glandular cells Low Enhanced P52732 +ENSG00000138160 KIF11 prostate glandular cells Low Enhanced P52732 +ENSG00000138160 KIF11 seminal vesicle glandular cells Low Enhanced P52732 +ENSG00000138160 KIF11 testis cells in seminiferous ducts High Enhanced P52732 +ENSG00000138160 KIF11 testis Leydig cells Low Enhanced P52732 +ENSG00000138162 TACC2 epididymis glandular cells Medium Enhanced O95359 +ENSG00000138162 TACC2 prostate glandular cells Medium Enhanced O95359 +ENSG00000138162 TACC2 seminal vesicle glandular cells Medium Enhanced O95359 +ENSG00000138162 TACC2 testis cells in seminiferous ducts Medium Enhanced O95359 +ENSG00000138162 TACC2 testis Leydig cells Medium Enhanced O95359 +ENSG00000138185 ENTPD1 epididymis glandular cells Medium Enhanced P49961 +ENSG00000138185 ENTPD1 seminal vesicle glandular cells Medium Enhanced P49961 +ENSG00000138185 ENTPD1 testis cells in seminiferous ducts Low Enhanced P49961 +ENSG00000138185 ENTPD1 testis Leydig cells Low Enhanced P49961 +ENSG00000138193 PLCE1 epididymis glandular cells Low Enhanced Q9P212 +ENSG00000138193 PLCE1 seminal vesicle glandular cells Medium Enhanced Q9P212 +ENSG00000138193 PLCE1 testis cells in seminiferous ducts Medium Enhanced Q9P212 +ENSG00000138193 PLCE1 testis Leydig cells Medium Enhanced Q9P212 +ENSG00000138207 RBP4 testis cells in seminiferous ducts Low Supported P02753 +ENSG00000138207 RBP4 testis Leydig cells Low Supported P02753 +ENSG00000138231 DBR1 epididymis glandular cells Medium Supported Q9UK59 +ENSG00000138231 DBR1 prostate glandular cells Medium Supported Q9UK59 +ENSG00000138231 DBR1 seminal vesicle glandular cells Medium Supported Q9UK59 +ENSG00000138231 DBR1 testis cells in seminiferous ducts Medium Supported Q9UK59 +ENSG00000138231 DBR1 testis Leydig cells Medium Supported Q9UK59 +ENSG00000138311 ZNF365 epididymis glandular cells Low Enhanced Q70YC4 +ENSG00000138356 AOX1 prostate glandular cells Low Enhanced Q06278 +ENSG00000138356 AOX1 seminal vesicle glandular cells Medium Enhanced Q06278 +ENSG00000138356 AOX1 testis Leydig cells Medium Enhanced Q06278 +ENSG00000138363 ATIC epididymis glandular cells High Supported P31939 +ENSG00000138363 ATIC prostate glandular cells Medium Supported P31939 +ENSG00000138363 ATIC testis cells in seminiferous ducts High Supported P31939 +ENSG00000138363 ATIC testis Leydig cells High Supported P31939 +ENSG00000138376 BARD1 epididymis glandular cells Medium Enhanced Q99728 +ENSG00000138376 BARD1 prostate glandular cells Low Enhanced Q99728 +ENSG00000138376 BARD1 seminal vesicle glandular cells Medium Enhanced Q99728 +ENSG00000138376 BARD1 testis cells in seminiferous ducts Medium Enhanced Q99728 +ENSG00000138376 BARD1 testis Leydig cells Low Enhanced Q99728 +ENSG00000138378 STAT4 epididymis glandular cells Low Enhanced Q14765 +ENSG00000138378 STAT4 prostate glandular cells Low Enhanced Q14765 +ENSG00000138378 STAT4 testis elongated or late spermatids Low Enhanced Q14765 +ENSG00000138378 STAT4 testis Leydig cells Low Enhanced Q14765 +ENSG00000138378 STAT4 testis pachytene spermatocytes Low Enhanced Q14765 +ENSG00000138378 STAT4 testis preleptotene spermatocytes Low Enhanced Q14765 +ENSG00000138378 STAT4 testis round or early spermatids High Enhanced Q14765 +ENSG00000138378 STAT4 testis spermatogonia Low Enhanced Q14765 +ENSG00000138385 SSB epididymis glandular cells High Supported P05455 +ENSG00000138385 SSB prostate glandular cells High Supported P05455 +ENSG00000138385 SSB seminal vesicle glandular cells High Supported P05455 +ENSG00000138385 SSB testis cells in seminiferous ducts High Supported P05455 +ENSG00000138385 SSB testis Leydig cells High Supported P05455 +ENSG00000138398 PPIG epididymis glandular cells High Supported Q13427 +ENSG00000138398 PPIG prostate glandular cells High Supported Q13427 +ENSG00000138398 PPIG seminal vesicle glandular cells High Supported Q13427 +ENSG00000138398 PPIG testis cells in seminiferous ducts High Supported Q13427 +ENSG00000138398 PPIG testis Leydig cells High Supported Q13427 +ENSG00000138413 IDH1 epididymis glandular cells High Enhanced O75874 +ENSG00000138413 IDH1 prostate glandular cells High Enhanced O75874 +ENSG00000138413 IDH1 seminal vesicle glandular cells High Enhanced O75874 +ENSG00000138413 IDH1 testis cells in seminiferous ducts High Enhanced O75874 +ENSG00000138413 IDH1 testis Leydig cells High Enhanced O75874 +ENSG00000138443 ABI2 testis cells in seminiferous ducts Low Enhanced Q9NYB9 +ENSG00000138448 ITGAV epididymis glandular cells Medium Supported P06756 +ENSG00000138448 ITGAV prostate glandular cells Medium Supported P06756 +ENSG00000138448 ITGAV seminal vesicle glandular cells High Supported P06756 +ENSG00000138448 ITGAV testis cells in seminiferous ducts Medium Supported P06756 +ENSG00000138448 ITGAV testis Leydig cells Medium Supported P06756 +ENSG00000138495 COX17 epididymis glandular cells Medium Supported Q14061 +ENSG00000138495 COX17 prostate glandular cells Medium Supported Q14061 +ENSG00000138495 COX17 seminal vesicle glandular cells High Supported Q14061 +ENSG00000138495 COX17 testis cells in seminiferous ducts High Supported Q14061 +ENSG00000138495 COX17 testis Leydig cells High Supported Q14061 +ENSG00000138600 SPPL2A epididymis glandular cells Medium Enhanced Q8TCT8 +ENSG00000138600 SPPL2A prostate glandular cells High Enhanced Q8TCT8 +ENSG00000138600 SPPL2A seminal vesicle glandular cells Medium Enhanced Q8TCT8 +ENSG00000138600 SPPL2A testis cells in seminiferous ducts Medium Enhanced Q8TCT8 +ENSG00000138600 SPPL2A testis Leydig cells Medium Enhanced Q8TCT8 +ENSG00000138646 HERC5 testis pachytene spermatocytes Medium Supported Q9UII4 +ENSG00000138646 HERC5 testis preleptotene spermatocytes High Supported Q9UII4 +ENSG00000138646 HERC5 testis spermatogonia High Supported Q9UII4 +ENSG00000138668 HNRNPD epididymis glandular cells Medium Supported Q14103 +ENSG00000138668 HNRNPD prostate glandular cells High Supported Q14103 +ENSG00000138668 HNRNPD seminal vesicle glandular cells High Supported Q14103 +ENSG00000138668 HNRNPD testis cells in seminiferous ducts High Supported Q14103 +ENSG00000138722 MMRN1 seminal vesicle glandular cells Low Enhanced Q13201 +ENSG00000138738 PRDM5 epididymis glandular cells High Enhanced Q9NQX1 +ENSG00000138738 PRDM5 prostate glandular cells High Enhanced Q9NQX1 +ENSG00000138738 PRDM5 seminal vesicle glandular cells High Enhanced Q9NQX1 +ENSG00000138738 PRDM5 testis cells in seminiferous ducts High Enhanced Q9NQX1 +ENSG00000138738 PRDM5 testis Leydig cells High Enhanced Q9NQX1 +ENSG00000138757 G3BP2 epididymis glandular cells High Enhanced Q9UN86 +ENSG00000138757 G3BP2 prostate glandular cells High Enhanced Q9UN86 +ENSG00000138757 G3BP2 seminal vesicle glandular cells Medium Enhanced Q9UN86 +ENSG00000138757 G3BP2 testis cells in seminiferous ducts High Enhanced Q9UN86 +ENSG00000138757 G3BP2 testis Leydig cells High Enhanced Q9UN86 +ENSG00000138760 SCARB2 epididymis glandular cells High Supported Q14108 +ENSG00000138760 SCARB2 prostate glandular cells High Supported Q14108 +ENSG00000138760 SCARB2 seminal vesicle glandular cells High Supported Q14108 +ENSG00000138760 SCARB2 testis cells in seminiferous ducts High Supported Q14108 +ENSG00000138760 SCARB2 testis Leydig cells High Supported Q14108 +ENSG00000138768 USO1 epididymis glandular cells High Supported O60763 +ENSG00000138768 USO1 prostate glandular cells Medium Supported O60763 +ENSG00000138768 USO1 seminal vesicle glandular cells Medium Supported O60763 +ENSG00000138768 USO1 testis cells in seminiferous ducts High Supported O60763 +ENSG00000138768 USO1 testis Leydig cells Medium Supported O60763 +ENSG00000138771 SHROOM3 epididymis glandular cells Medium Enhanced Q8TF72 +ENSG00000138771 SHROOM3 prostate glandular cells Medium Enhanced Q8TF72 +ENSG00000138771 SHROOM3 seminal vesicle glandular cells Medium Enhanced Q8TF72 +ENSG00000138771 SHROOM3 testis Leydig cells Low Enhanced Q8TF72 +ENSG00000138772 ANXA3 epididymis glandular cells Low Enhanced P12429 +ENSG00000138772 ANXA3 prostate glandular cells Medium Enhanced P12429 +ENSG00000138772 ANXA3 seminal vesicle glandular cells Medium Enhanced P12429 +ENSG00000138772 ANXA3 testis Leydig cells Low Enhanced P12429 +ENSG00000138777 PPA2 epididymis glandular cells Medium Supported Q9H2U2 +ENSG00000138777 PPA2 prostate glandular cells High Supported Q9H2U2 +ENSG00000138777 PPA2 seminal vesicle glandular cells Medium Supported Q9H2U2 +ENSG00000138777 PPA2 testis cells in seminiferous ducts Medium Supported Q9H2U2 +ENSG00000138777 PPA2 testis Leydig cells High Supported Q9H2U2 +ENSG00000138792 ENPEP epididymis glandular cells Low Enhanced Q07075 +ENSG00000138792 ENPEP seminal vesicle glandular cells Low Enhanced Q07075 +ENSG00000138792 ENPEP testis Leydig cells Low Enhanced Q07075 +ENSG00000138794 CASP6 prostate glandular cells Low Enhanced P55212 +ENSG00000138794 CASP6 seminal vesicle glandular cells Low Enhanced P55212 +ENSG00000138796 HADH epididymis glandular cells Medium Supported Q16836 +ENSG00000138796 HADH prostate glandular cells High Supported Q16836 +ENSG00000138796 HADH seminal vesicle glandular cells High Supported Q16836 +ENSG00000138796 HADH testis cells in seminiferous ducts High Supported Q16836 +ENSG00000138796 HADH testis Leydig cells High Supported Q16836 +ENSG00000138814 PPP3CA epididymis glandular cells Low Enhanced Q08209 +ENSG00000138814 PPP3CA prostate glandular cells Medium Enhanced Q08209 +ENSG00000138814 PPP3CA testis Leydig cells Medium Enhanced Q08209 +ENSG00000139044 B4GALNT3 epididymis glandular cells Low Enhanced Q6L9W6 +ENSG00000139044 B4GALNT3 seminal vesicle glandular cells Medium Enhanced Q6L9W6 +ENSG00000139044 B4GALNT3 testis cells in seminiferous ducts Low Enhanced Q6L9W6 +ENSG00000139044 B4GALNT3 testis Leydig cells Medium Enhanced Q6L9W6 +ENSG00000139083 ETV6 epididymis glandular cells Low Enhanced P41212 +ENSG00000139083 ETV6 prostate glandular cells Medium Enhanced P41212 +ENSG00000139083 ETV6 seminal vesicle glandular cells Medium Enhanced P41212 +ENSG00000139083 ETV6 testis cells in seminiferous ducts Medium Enhanced P41212 +ENSG00000139116 KIF21A prostate glandular cells Low Enhanced Q7Z4S6 +ENSG00000139116 KIF21A seminal vesicle glandular cells Low Enhanced Q7Z4S6 +ENSG00000139116 KIF21A testis cells in seminiferous ducts Medium Enhanced Q7Z4S6 +ENSG00000139116 KIF21A testis Leydig cells Low Enhanced Q7Z4S6 +ENSG00000139174 PRICKLE1 epididymis glandular cells Medium Enhanced Q96MT3 +ENSG00000139174 PRICKLE1 prostate glandular cells Low Enhanced Q96MT3 +ENSG00000139174 PRICKLE1 testis cells in seminiferous ducts Medium Enhanced Q96MT3 +ENSG00000139174 PRICKLE1 testis Leydig cells Medium Enhanced Q96MT3 +ENSG00000139178 C1RL epididymis glandular cells Medium Supported Q9NZP8 +ENSG00000139178 C1RL seminal vesicle glandular cells Low Supported Q9NZP8 +ENSG00000139178 C1RL testis cells in seminiferous ducts Low Supported Q9NZP8 +ENSG00000139178 C1RL testis Leydig cells Low Supported Q9NZP8 +ENSG00000139180 NDUFA9 epididymis glandular cells Medium Enhanced Q16795 +ENSG00000139180 NDUFA9 prostate glandular cells High Enhanced Q16795 +ENSG00000139180 NDUFA9 seminal vesicle glandular cells High Enhanced Q16795 +ENSG00000139180 NDUFA9 testis cells in seminiferous ducts Low Enhanced Q16795 +ENSG00000139180 NDUFA9 testis Leydig cells High Enhanced Q16795 +ENSG00000139194 RBP5 epididymis glandular cells Medium Enhanced P82980 +ENSG00000139194 RBP5 prostate glandular cells Medium Enhanced P82980 +ENSG00000139194 RBP5 seminal vesicle glandular cells Medium Enhanced P82980 +ENSG00000139194 RBP5 testis cells in seminiferous ducts Medium Enhanced P82980 +ENSG00000139194 RBP5 testis Leydig cells Medium Enhanced P82980 +ENSG00000139197 PEX5 epididymis glandular cells High Enhanced P50542 +ENSG00000139197 PEX5 prostate glandular cells Medium Enhanced P50542 +ENSG00000139197 PEX5 seminal vesicle glandular cells Medium Enhanced P50542 +ENSG00000139197 PEX5 testis cells in seminiferous ducts High Enhanced P50542 +ENSG00000139197 PEX5 testis Leydig cells High Enhanced P50542 +ENSG00000139218 SCAF11 epididymis glandular cells Medium Enhanced Q99590 +ENSG00000139218 SCAF11 prostate glandular cells Medium Enhanced Q99590 +ENSG00000139218 SCAF11 seminal vesicle glandular cells Medium Enhanced Q99590 +ENSG00000139218 SCAF11 testis cells in seminiferous ducts Medium Enhanced Q99590 +ENSG00000139218 SCAF11 testis Leydig cells Medium Enhanced Q99590 +ENSG00000139351 SYCP3 testis Leydig cells Low Enhanced Q8IZU3 +ENSG00000139351 SYCP3 testis pachytene spermatocytes High Enhanced Q8IZU3 +ENSG00000139372 TDG epididymis glandular cells High Supported Q13569 +ENSG00000139372 TDG prostate glandular cells Medium Supported Q13569 +ENSG00000139372 TDG seminal vesicle glandular cells Medium Supported Q13569 +ENSG00000139372 TDG testis cells in seminiferous ducts High Supported Q13569 +ENSG00000139372 TDG testis Leydig cells High Supported Q13569 +ENSG00000139405 RITA1 epididymis glandular cells High Supported Q96K30 +ENSG00000139405 RITA1 prostate glandular cells Medium Supported Q96K30 +ENSG00000139405 RITA1 seminal vesicle glandular cells High Supported Q96K30 +ENSG00000139405 RITA1 testis cells in seminiferous ducts Medium Supported Q96K30 +ENSG00000139405 RITA1 testis Leydig cells Medium Supported Q96K30 +ENSG00000139437 TCHP prostate glandular cells Medium Supported Q9BT92 +ENSG00000139437 TCHP testis cells in seminiferous ducts Low Supported Q9BT92 +ENSG00000139437 TCHP testis Leydig cells Low Supported Q9BT92 +ENSG00000139572 GPR84 seminal vesicle glandular cells Low Enhanced Q9NQS5 +ENSG00000139579 NABP2 epididymis glandular cells High Supported Q9BQ15 +ENSG00000139579 NABP2 prostate glandular cells Low Supported Q9BQ15 +ENSG00000139579 NABP2 seminal vesicle glandular cells Medium Supported Q9BQ15 +ENSG00000139579 NABP2 testis cells in seminiferous ducts Low Supported Q9BQ15 +ENSG00000139579 NABP2 testis Leydig cells Low Supported Q9BQ15 +ENSG00000139613 SMARCC2 epididymis glandular cells High Supported Q8TAQ2 +ENSG00000139613 SMARCC2 prostate glandular cells High Supported Q8TAQ2 +ENSG00000139613 SMARCC2 seminal vesicle glandular cells High Supported Q8TAQ2 +ENSG00000139613 SMARCC2 testis cells in seminiferous ducts High Supported Q8TAQ2 +ENSG00000139613 SMARCC2 testis Leydig cells High Supported Q8TAQ2 +ENSG00000139629 GALNT6 epididymis glandular cells High Enhanced Q8NCL4 +ENSG00000139629 GALNT6 seminal vesicle glandular cells Medium Enhanced Q8NCL4 +ENSG00000139629 GALNT6 testis cells in seminiferous ducts Medium Enhanced Q8NCL4 +ENSG00000139629 GALNT6 testis Leydig cells Low Enhanced Q8NCL4 +ENSG00000139656 SMIM2 testis Leydig cells Medium Enhanced Q9BVW6 +ENSG00000139687 RB1 epididymis glandular cells Medium Supported P06400 +ENSG00000139687 RB1 prostate glandular cells Low Supported P06400 +ENSG00000139687 RB1 seminal vesicle glandular cells Medium Supported P06400 +ENSG00000139687 RB1 testis cells in seminiferous ducts Medium Supported P06400 +ENSG00000139687 RB1 testis Leydig cells Medium Supported P06400 +ENSG00000139722 VPS37B epididymis glandular cells Medium Enhanced Q9H9H4 +ENSG00000139722 VPS37B prostate glandular cells Medium Enhanced Q9H9H4 +ENSG00000139722 VPS37B seminal vesicle glandular cells Medium Enhanced Q9H9H4 +ENSG00000139722 VPS37B testis cells in seminiferous ducts Medium Enhanced Q9H9H4 +ENSG00000139722 VPS37B testis Leydig cells Medium Enhanced Q9H9H4 +ENSG00000139725 RHOF epididymis glandular cells Medium Enhanced Q9HBH0 +ENSG00000139725 RHOF testis cells in seminiferous ducts Low Enhanced Q9HBH0 +ENSG00000139908 TSSK4 epididymis glandular cells Low Enhanced Q6SA08 +ENSG00000139908 TSSK4 testis cells in seminiferous ducts Medium Enhanced Q6SA08 +ENSG00000139971 C14orf37 epididymis glandular cells Low Enhanced Q86TY3 +ENSG00000139971 C14orf37 prostate glandular cells Medium Enhanced Q86TY3 +ENSG00000139971 C14orf37 seminal vesicle glandular cells Medium Enhanced Q86TY3 +ENSG00000139971 C14orf37 testis cells in seminiferous ducts Low Enhanced Q86TY3 +ENSG00000140009 ESR2 testis Leydig cells Low Enhanced Q92731 +ENSG00000140022 STON2 epididymis glandular cells Medium Enhanced Q8WXE9 +ENSG00000140022 STON2 prostate glandular cells Low Enhanced Q8WXE9 +ENSG00000140022 STON2 seminal vesicle glandular cells Low Enhanced Q8WXE9 +ENSG00000140022 STON2 testis cells in seminiferous ducts Medium Enhanced Q8WXE9 +ENSG00000140022 STON2 testis Leydig cells Low Enhanced Q8WXE9 +ENSG00000140044 JDP2 epididymis glandular cells High Supported Q8WYK2 +ENSG00000140044 JDP2 prostate glandular cells Low Supported Q8WYK2 +ENSG00000140044 JDP2 seminal vesicle glandular cells High Supported Q8WYK2 +ENSG00000140044 JDP2 testis cells in seminiferous ducts Medium Supported Q8WYK2 +ENSG00000140044 JDP2 testis Leydig cells High Supported Q8WYK2 +ENSG00000140057 AK7 epididymis glandular cells Low Enhanced Q96M32 +ENSG00000140057 AK7 prostate glandular cells Low Enhanced Q96M32 +ENSG00000140057 AK7 seminal vesicle glandular cells Low Enhanced Q96M32 +ENSG00000140057 AK7 testis cells in seminiferous ducts Low Enhanced Q96M32 +ENSG00000140057 AK7 testis Leydig cells Low Enhanced Q96M32 +ENSG00000140067 FAM181A testis elongated or late spermatids Low Enhanced NA +ENSG00000140067 FAM181A testis pachytene spermatocytes High Enhanced NA +ENSG00000140067 FAM181A testis round or early spermatids High Enhanced NA +ENSG00000140263 SORD prostate glandular cells High Enhanced Q00796 +ENSG00000140263 SORD seminal vesicle glandular cells High Enhanced Q00796 +ENSG00000140263 SORD testis Leydig cells Low Enhanced Q00796 +ENSG00000140265 ZSCAN29 epididymis glandular cells Medium Enhanced Q8IWY8 +ENSG00000140265 ZSCAN29 prostate glandular cells High Enhanced Q8IWY8 +ENSG00000140265 ZSCAN29 seminal vesicle glandular cells High Enhanced Q8IWY8 +ENSG00000140265 ZSCAN29 testis cells in seminiferous ducts Medium Enhanced Q8IWY8 +ENSG00000140265 ZSCAN29 testis Leydig cells High Enhanced Q8IWY8 +ENSG00000140284 SLC27A2 epididymis glandular cells Medium Enhanced O14975 +ENSG00000140284 SLC27A2 seminal vesicle glandular cells Low Enhanced O14975 +ENSG00000140326 CDAN1 epididymis glandular cells High Enhanced Q8IWY9 +ENSG00000140326 CDAN1 prostate glandular cells Medium Enhanced Q8IWY9 +ENSG00000140326 CDAN1 seminal vesicle glandular cells High Enhanced Q8IWY9 +ENSG00000140326 CDAN1 testis cells in seminiferous ducts Medium Enhanced Q8IWY9 +ENSG00000140350 ANP32A epididymis glandular cells High Supported P39687 +ENSG00000140350 ANP32A prostate glandular cells High Supported P39687 +ENSG00000140350 ANP32A seminal vesicle glandular cells High Supported P39687 +ENSG00000140350 ANP32A testis cells in seminiferous ducts Medium Supported P39687 +ENSG00000140350 ANP32A testis Leydig cells High Supported P39687 +ENSG00000140374 ETFA epididymis glandular cells Low Enhanced P13804 +ENSG00000140374 ETFA prostate glandular cells Medium Enhanced P13804 +ENSG00000140374 ETFA seminal vesicle glandular cells Medium Enhanced P13804 +ENSG00000140374 ETFA testis cells in seminiferous ducts Medium Enhanced P13804 +ENSG00000140374 ETFA testis Leydig cells High Enhanced P13804 +ENSG00000140382 HMG20A epididymis glandular cells Medium Supported Q9NP66 +ENSG00000140382 HMG20A prostate glandular cells Medium Supported Q9NP66 +ENSG00000140382 HMG20A seminal vesicle glandular cells Medium Supported Q9NP66 +ENSG00000140382 HMG20A testis cells in seminiferous ducts High Supported Q9NP66 +ENSG00000140382 HMG20A testis Leydig cells Medium Supported Q9NP66 +ENSG00000140395 WDR61 epididymis glandular cells Medium Enhanced Q9GZS3 +ENSG00000140395 WDR61 prostate glandular cells Medium Enhanced Q9GZS3 +ENSG00000140395 WDR61 seminal vesicle glandular cells Medium Enhanced Q9GZS3 +ENSG00000140395 WDR61 testis cells in seminiferous ducts Medium Enhanced Q9GZS3 +ENSG00000140395 WDR61 testis Leydig cells Medium Enhanced Q9GZS3 +ENSG00000140416 TPM1 epididymis glandular cells Low Supported P09493 +ENSG00000140416 TPM1 testis Leydig cells Low Supported P09493 +ENSG00000140451 PIF1 epididymis glandular cells High Supported Q9H611 +ENSG00000140451 PIF1 prostate glandular cells High Supported Q9H611 +ENSG00000140451 PIF1 seminal vesicle glandular cells High Supported Q9H611 +ENSG00000140451 PIF1 testis cells in seminiferous ducts High Supported Q9H611 +ENSG00000140451 PIF1 testis Leydig cells High Supported Q9H611 +ENSG00000140459 CYP11A1 testis cells in seminiferous ducts Low Enhanced P05108 +ENSG00000140459 CYP11A1 testis Leydig cells High Enhanced P05108 +ENSG00000140464 PML epididymis glandular cells Medium Supported P29590 +ENSG00000140464 PML prostate glandular cells Low Supported P29590 +ENSG00000140464 PML seminal vesicle glandular cells Medium Supported P29590 +ENSG00000140464 PML testis cells in seminiferous ducts Medium Supported P29590 +ENSG00000140464 PML testis Leydig cells Medium Supported P29590 +ENSG00000140478 GOLGA6D testis elongated or late spermatids High Supported P0CG33 +ENSG00000140478 GOLGA6D testis round or early spermatids High Supported P0CG33 +ENSG00000140478 GOLGA6D testis spermatogonia High Supported P0CG33 +ENSG00000140538 NTRK3 epididymis glandular cells Low Enhanced Q16288 +ENSG00000140538 NTRK3 prostate glandular cells Low Enhanced Q16288 +ENSG00000140538 NTRK3 testis cells in seminiferous ducts Low Enhanced Q16288 +ENSG00000140538 NTRK3 testis Leydig cells Medium Enhanced Q16288 +ENSG00000140548 ZNF710 epididymis glandular cells Medium Enhanced Q8N1W2 +ENSG00000140548 ZNF710 prostate glandular cells High Enhanced Q8N1W2 +ENSG00000140548 ZNF710 seminal vesicle glandular cells Low Enhanced Q8N1W2 +ENSG00000140548 ZNF710 testis cells in seminiferous ducts Low Enhanced Q8N1W2 +ENSG00000140548 ZNF710 testis Leydig cells Medium Enhanced Q8N1W2 +ENSG00000140575 IQGAP1 epididymis glandular cells Medium Enhanced P46940 +ENSG00000140575 IQGAP1 prostate glandular cells Medium Enhanced P46940 +ENSG00000140575 IQGAP1 seminal vesicle glandular cells Medium Enhanced P46940 +ENSG00000140575 IQGAP1 testis cells in seminiferous ducts Low Enhanced P46940 +ENSG00000140575 IQGAP1 testis Leydig cells Low Enhanced P46940 +ENSG00000140600 SH3GL3 testis elongated or late spermatids High Enhanced Q99963 +ENSG00000140632 GLYR1 epididymis glandular cells High Enhanced Q49A26 +ENSG00000140632 GLYR1 prostate glandular cells High Enhanced Q49A26 +ENSG00000140632 GLYR1 seminal vesicle glandular cells High Enhanced Q49A26 +ENSG00000140632 GLYR1 testis cells in seminiferous ducts High Enhanced Q49A26 +ENSG00000140632 GLYR1 testis Leydig cells High Enhanced Q49A26 +ENSG00000140675 SLC5A2 testis cells in seminiferous ducts Low Enhanced P31639 +ENSG00000140682 TGFB1I1 prostate glandular cells Low Enhanced O43294 +ENSG00000140682 TGFB1I1 testis Leydig cells Low Enhanced O43294 +ENSG00000140694 PARN epididymis glandular cells High Enhanced NA +ENSG00000140694 PARN prostate glandular cells High Enhanced NA +ENSG00000140694 PARN testis cells in seminiferous ducts High Enhanced NA +ENSG00000140694 PARN testis Leydig cells High Enhanced NA +ENSG00000140718 FTO epididymis glandular cells High Enhanced Q9C0B1 +ENSG00000140718 FTO prostate glandular cells Medium Enhanced Q9C0B1 +ENSG00000140718 FTO seminal vesicle glandular cells Medium Enhanced Q9C0B1 +ENSG00000140718 FTO testis cells in seminiferous ducts Low Enhanced Q9C0B1 +ENSG00000140718 FTO testis Leydig cells High Enhanced Q9C0B1 +ENSG00000140740 UQCRC2 epididymis glandular cells Low Enhanced H3BUI9 +ENSG00000140740 UQCRC2 prostate glandular cells Medium Enhanced H3BUI9 +ENSG00000140740 UQCRC2 seminal vesicle glandular cells Medium Enhanced H3BUI9 +ENSG00000140740 UQCRC2 testis cells in seminiferous ducts Medium Enhanced H3BUI9 +ENSG00000140740 UQCRC2 testis Leydig cells Medium Enhanced H3BUI9 +ENSG00000140795 MYLK3 testis cells in seminiferous ducts Low Enhanced Q32MK0 +ENSG00000140854 KATNB1 epididymis glandular cells Low Enhanced Q9BVA0 +ENSG00000140854 KATNB1 prostate glandular cells Medium Enhanced Q9BVA0 +ENSG00000140854 KATNB1 seminal vesicle glandular cells Low Enhanced Q9BVA0 +ENSG00000140854 KATNB1 testis cells in seminiferous ducts Medium Enhanced Q9BVA0 +ENSG00000140854 KATNB1 testis Leydig cells Low Enhanced Q9BVA0 +ENSG00000140876 NUDT7 epididymis glandular cells Medium Supported P0C024 +ENSG00000140876 NUDT7 prostate glandular cells Medium Supported P0C024 +ENSG00000140876 NUDT7 seminal vesicle glandular cells Medium Supported P0C024 +ENSG00000140876 NUDT7 testis cells in seminiferous ducts Low Supported P0C024 +ENSG00000140876 NUDT7 testis Leydig cells High Supported P0C024 +ENSG00000140937 CDH11 prostate glandular cells Low Enhanced P55287 +ENSG00000140939 NOL3 epididymis glandular cells Medium Enhanced O60936 +ENSG00000140939 NOL3 prostate glandular cells High Enhanced O60936 +ENSG00000140939 NOL3 seminal vesicle glandular cells Medium Enhanced O60936 +ENSG00000140939 NOL3 testis cells in seminiferous ducts Low Enhanced O60936 +ENSG00000140939 NOL3 testis Leydig cells Medium Enhanced O60936 +ENSG00000140943 MBTPS1 epididymis glandular cells High Supported Q14703 +ENSG00000140943 MBTPS1 seminal vesicle glandular cells Medium Supported Q14703 +ENSG00000140943 MBTPS1 testis cells in seminiferous ducts Medium Supported Q14703 +ENSG00000140943 MBTPS1 testis Leydig cells Low Supported Q14703 +ENSG00000140990 NDUFB10 epididymis glandular cells Medium Enhanced O96000 +ENSG00000140990 NDUFB10 seminal vesicle glandular cells High Enhanced O96000 +ENSG00000140990 NDUFB10 testis cells in seminiferous ducts Medium Enhanced O96000 +ENSG00000140990 NDUFB10 testis Leydig cells High Enhanced O96000 +ENSG00000140992 PDPK1 epididymis glandular cells Medium Supported O15530 +ENSG00000140992 PDPK1 prostate glandular cells Low Supported O15530 +ENSG00000140992 PDPK1 seminal vesicle glandular cells Low Supported O15530 +ENSG00000140992 PDPK1 testis cells in seminiferous ducts Medium Supported O15530 +ENSG00000140992 PDPK1 testis Leydig cells Medium Supported O15530 +ENSG00000141002 TCF25 epididymis glandular cells High Enhanced Q9BQ70 +ENSG00000141002 TCF25 prostate glandular cells High Enhanced Q9BQ70 +ENSG00000141002 TCF25 seminal vesicle glandular cells High Enhanced Q9BQ70 +ENSG00000141002 TCF25 testis cells in seminiferous ducts Medium Enhanced Q9BQ70 +ENSG00000141002 TCF25 testis Leydig cells High Enhanced Q9BQ70 +ENSG00000141012 GALNS epididymis glandular cells High Enhanced P34059 +ENSG00000141012 GALNS prostate glandular cells High Enhanced P34059 +ENSG00000141012 GALNS seminal vesicle glandular cells High Enhanced P34059 +ENSG00000141012 GALNS testis cells in seminiferous ducts Medium Enhanced P34059 +ENSG00000141012 GALNS testis Leydig cells Medium Enhanced P34059 +ENSG00000141027 NCOR1 epididymis glandular cells Medium Enhanced O75376 +ENSG00000141027 NCOR1 prostate glandular cells Medium Enhanced O75376 +ENSG00000141027 NCOR1 seminal vesicle glandular cells Medium Enhanced O75376 +ENSG00000141027 NCOR1 testis cells in seminiferous ducts Medium Enhanced O75376 +ENSG00000141027 NCOR1 testis Leydig cells Medium Enhanced O75376 +ENSG00000141096 DPEP3 testis elongated or late spermatids High Enhanced Q9H4B8 +ENSG00000141096 DPEP3 testis pachytene spermatocytes High Enhanced Q9H4B8 +ENSG00000141096 DPEP3 testis preleptotene spermatocytes Low Enhanced Q9H4B8 +ENSG00000141096 DPEP3 testis round or early spermatids High Enhanced Q9H4B8 +ENSG00000141252 VPS53 epididymis glandular cells Medium Enhanced E7EVT8 +ENSG00000141252 VPS53 prostate glandular cells Medium Enhanced E7EVT8 +ENSG00000141252 VPS53 seminal vesicle glandular cells Medium Enhanced E7EVT8 +ENSG00000141252 VPS53 testis cells in seminiferous ducts Medium Enhanced E7EVT8 +ENSG00000141252 VPS53 testis Leydig cells Medium Enhanced E7EVT8 +ENSG00000141294 LRRC46 testis cells in seminiferous ducts Medium Enhanced Q96FV0 +ENSG00000141294 LRRC46 testis Leydig cells Low Enhanced Q96FV0 +ENSG00000141295 SCRN2 epididymis glandular cells Low Enhanced Q96FV2 +ENSG00000141295 SCRN2 prostate glandular cells Low Enhanced Q96FV2 +ENSG00000141295 SCRN2 seminal vesicle glandular cells Medium Enhanced Q96FV2 +ENSG00000141295 SCRN2 testis cells in seminiferous ducts Low Enhanced Q96FV2 +ENSG00000141295 SCRN2 testis Leydig cells Medium Enhanced Q96FV2 +ENSG00000141316 SPACA3 testis elongated or late spermatids Medium Enhanced Q8IXA5 +ENSG00000141316 SPACA3 testis round or early spermatids High Enhanced Q8IXA5 +ENSG00000141337 ARSG epididymis glandular cells Low Enhanced Q96EG1 +ENSG00000141337 ARSG seminal vesicle glandular cells Low Enhanced Q96EG1 +ENSG00000141337 ARSG testis Leydig cells Low Enhanced Q96EG1 +ENSG00000141338 ABCA8 testis cells in seminiferous ducts Medium Enhanced O94911 +ENSG00000141338 ABCA8 testis Leydig cells High Enhanced O94911 +ENSG00000141371 C17orf64 testis elongated or late spermatids Medium Enhanced Q86WR6 +ENSG00000141371 C17orf64 testis pachytene spermatocytes Medium Enhanced Q86WR6 +ENSG00000141371 C17orf64 testis round or early spermatids High Enhanced Q86WR6 +ENSG00000141378 PTRH2 epididymis glandular cells High Supported Q9Y3E5 +ENSG00000141378 PTRH2 prostate glandular cells High Supported Q9Y3E5 +ENSG00000141378 PTRH2 seminal vesicle glandular cells High Supported Q9Y3E5 +ENSG00000141378 PTRH2 testis cells in seminiferous ducts Medium Supported Q9Y3E5 +ENSG00000141378 PTRH2 testis Leydig cells High Supported Q9Y3E5 +ENSG00000141380 SS18 epididymis glandular cells Low Supported Q15532 +ENSG00000141380 SS18 prostate glandular cells Low Supported Q15532 +ENSG00000141380 SS18 seminal vesicle glandular cells Medium Supported Q15532 +ENSG00000141380 SS18 testis cells in seminiferous ducts Medium Supported Q15532 +ENSG00000141380 SS18 testis Leydig cells Low Supported Q15532 +ENSG00000141385 AFG3L2 epididymis glandular cells High Enhanced Q9Y4W6 +ENSG00000141385 AFG3L2 prostate glandular cells Medium Enhanced Q9Y4W6 +ENSG00000141385 AFG3L2 seminal vesicle glandular cells High Enhanced Q9Y4W6 +ENSG00000141385 AFG3L2 testis cells in seminiferous ducts High Enhanced Q9Y4W6 +ENSG00000141385 AFG3L2 testis Leydig cells High Enhanced Q9Y4W6 +ENSG00000141404 GNAL epididymis glandular cells Medium Supported P38405 +ENSG00000141404 GNAL prostate glandular cells Medium Supported P38405 +ENSG00000141404 GNAL seminal vesicle glandular cells Medium Supported P38405 +ENSG00000141404 GNAL testis Leydig cells Medium Supported P38405 +ENSG00000141425 RPRD1A epididymis glandular cells High Supported Q96P16 +ENSG00000141425 RPRD1A prostate glandular cells High Supported Q96P16 +ENSG00000141425 RPRD1A seminal vesicle glandular cells High Supported Q96P16 +ENSG00000141425 RPRD1A testis cells in seminiferous ducts High Supported Q96P16 +ENSG00000141425 RPRD1A testis Leydig cells High Supported Q96P16 +ENSG00000141447 OSBPL1A prostate glandular cells Medium Supported Q9BXW6 +ENSG00000141447 OSBPL1A seminal vesicle glandular cells Medium Supported Q9BXW6 +ENSG00000141447 OSBPL1A testis cells in seminiferous ducts Medium Supported Q9BXW6 +ENSG00000141447 OSBPL1A testis Leydig cells Medium Supported Q9BXW6 +ENSG00000141456 PELP1 epididymis glandular cells High Supported Q8IZL8 +ENSG00000141456 PELP1 prostate glandular cells Medium Supported Q8IZL8 +ENSG00000141456 PELP1 seminal vesicle glandular cells High Supported Q8IZL8 +ENSG00000141456 PELP1 testis cells in seminiferous ducts High Supported Q8IZL8 +ENSG00000141456 PELP1 testis Leydig cells High Supported Q8IZL8 +ENSG00000141469 SLC14A1 prostate glandular cells Medium Supported Q13336 +ENSG00000141469 SLC14A1 testis cells in seminiferous ducts Low Supported Q13336 +ENSG00000141499 WRAP53 epididymis glandular cells Medium Enhanced Q9BUR4 +ENSG00000141499 WRAP53 prostate glandular cells Medium Enhanced Q9BUR4 +ENSG00000141499 WRAP53 seminal vesicle glandular cells Medium Enhanced Q9BUR4 +ENSG00000141499 WRAP53 testis cells in seminiferous ducts Medium Enhanced Q9BUR4 +ENSG00000141499 WRAP53 testis Leydig cells Medium Enhanced Q9BUR4 +ENSG00000141504 SAT2 testis Leydig cells Low Enhanced Q96F10 +ENSG00000141519 CCDC40 testis Leydig cells Low Enhanced Q4G0X9 +ENSG00000141543 EIF4A3 epididymis glandular cells High Enhanced P38919 +ENSG00000141543 EIF4A3 prostate glandular cells High Enhanced P38919 +ENSG00000141543 EIF4A3 seminal vesicle glandular cells Medium Enhanced P38919 +ENSG00000141543 EIF4A3 testis cells in seminiferous ducts High Enhanced P38919 +ENSG00000141543 EIF4A3 testis Leydig cells High Enhanced P38919 +ENSG00000141570 CBX8 epididymis glandular cells Medium Enhanced Q9HC52 +ENSG00000141570 CBX8 prostate glandular cells Medium Enhanced Q9HC52 +ENSG00000141570 CBX8 seminal vesicle glandular cells Medium Enhanced Q9HC52 +ENSG00000141570 CBX8 testis cells in seminiferous ducts High Enhanced Q9HC52 +ENSG00000141570 CBX8 testis Leydig cells Medium Enhanced Q9HC52 +ENSG00000141579 ZNF750 testis cells in seminiferous ducts Low Enhanced Q32MQ0 +ENSG00000141579 ZNF750 testis Leydig cells Low Enhanced Q32MQ0 +ENSG00000141736 ERBB2 prostate glandular cells Low Enhanced P04626 +ENSG00000141736 ERBB2 seminal vesicle glandular cells Low Enhanced P04626 +ENSG00000141756 FKBP10 epididymis glandular cells Low Enhanced Q96AY3 +ENSG00000141756 FKBP10 prostate glandular cells Low Enhanced Q96AY3 +ENSG00000141756 FKBP10 seminal vesicle glandular cells Low Enhanced Q96AY3 +ENSG00000141756 FKBP10 testis cells in seminiferous ducts Low Enhanced Q96AY3 +ENSG00000141756 FKBP10 testis Leydig cells Low Enhanced Q96AY3 +ENSG00000141867 BRD4 epididymis glandular cells High Enhanced O60885 +ENSG00000141867 BRD4 prostate glandular cells High Enhanced O60885 +ENSG00000141867 BRD4 seminal vesicle glandular cells High Enhanced O60885 +ENSG00000141867 BRD4 testis cells in seminiferous ducts High Enhanced O60885 +ENSG00000141867 BRD4 testis Leydig cells High Enhanced O60885 +ENSG00000141905 NFIC epididymis glandular cells Medium Supported P08651 +ENSG00000141905 NFIC prostate glandular cells Low Supported P08651 +ENSG00000141905 NFIC seminal vesicle glandular cells Medium Supported P08651 +ENSG00000141905 NFIC testis cells in seminiferous ducts High Supported P08651 +ENSG00000141905 NFIC testis Leydig cells High Supported P08651 +ENSG00000141968 VAV1 testis cells in seminiferous ducts Low Enhanced P15498 +ENSG00000142039 CCDC97 epididymis glandular cells High Enhanced Q96F63 +ENSG00000142039 CCDC97 prostate glandular cells Medium Enhanced Q96F63 +ENSG00000142039 CCDC97 seminal vesicle glandular cells Medium Enhanced Q96F63 +ENSG00000142039 CCDC97 testis cells in seminiferous ducts High Enhanced Q96F63 +ENSG00000142156 COL6A1 testis Leydig cells Low Enhanced P12109 +ENSG00000142168 SOD1 epididymis glandular cells Medium Enhanced P00441 +ENSG00000142168 SOD1 prostate glandular cells Medium Enhanced P00441 +ENSG00000142168 SOD1 seminal vesicle glandular cells Medium Enhanced P00441 +ENSG00000142168 SOD1 testis cells in seminiferous ducts Medium Enhanced P00441 +ENSG00000142168 SOD1 testis Leydig cells Medium Enhanced P00441 +ENSG00000142173 COL6A2 epididymis glandular cells Low Enhanced P12110 +ENSG00000142185 TRPM2 testis cells in seminiferous ducts Medium Enhanced O94759 +ENSG00000142185 TRPM2 testis Leydig cells Medium Enhanced O94759 +ENSG00000142192 APP epididymis glandular cells Low Enhanced P05067 +ENSG00000142192 APP prostate glandular cells Low Enhanced P05067 +ENSG00000142192 APP seminal vesicle glandular cells Low Enhanced P05067 +ENSG00000142192 APP testis cells in seminiferous ducts Low Enhanced P05067 +ENSG00000142207 URB1 epididymis glandular cells High Supported O60287 +ENSG00000142207 URB1 prostate glandular cells High Supported O60287 +ENSG00000142207 URB1 seminal vesicle glandular cells High Supported O60287 +ENSG00000142207 URB1 testis cells in seminiferous ducts Medium Supported O60287 +ENSG00000142207 URB1 testis Leydig cells High Supported O60287 +ENSG00000142208 AKT1 epididymis glandular cells High Enhanced P31749 +ENSG00000142208 AKT1 prostate glandular cells Medium Enhanced P31749 +ENSG00000142208 AKT1 seminal vesicle glandular cells High Enhanced P31749 +ENSG00000142208 AKT1 testis cells in seminiferous ducts High Enhanced P31749 +ENSG00000142208 AKT1 testis Leydig cells Medium Enhanced P31749 +ENSG00000142230 SAE1 epididymis glandular cells Low Enhanced Q9UBE0 +ENSG00000142230 SAE1 prostate glandular cells Low Enhanced Q9UBE0 +ENSG00000142230 SAE1 seminal vesicle glandular cells Medium Enhanced Q9UBE0 +ENSG00000142230 SAE1 testis cells in seminiferous ducts High Enhanced Q9UBE0 +ENSG00000142230 SAE1 testis Leydig cells Medium Enhanced Q9UBE0 +ENSG00000142409 ZNF787 epididymis glandular cells Medium Supported Q6DD87 +ENSG00000142409 ZNF787 prostate glandular cells Medium Supported Q6DD87 +ENSG00000142409 ZNF787 seminal vesicle glandular cells Medium Supported Q6DD87 +ENSG00000142409 ZNF787 testis cells in seminiferous ducts Low Supported Q6DD87 +ENSG00000142409 ZNF787 testis Leydig cells Medium Supported Q6DD87 +ENSG00000142453 CARM1 epididymis glandular cells Low Supported Q86X55 +ENSG00000142453 CARM1 prostate glandular cells Medium Supported Q86X55 +ENSG00000142453 CARM1 seminal vesicle glandular cells Medium Supported Q86X55 +ENSG00000142453 CARM1 testis cells in seminiferous ducts Medium Supported Q86X55 +ENSG00000142453 CARM1 testis Leydig cells Medium Supported Q86X55 +ENSG00000142494 SLC47A1 prostate glandular cells Low Enhanced Q96FL8 +ENSG00000142494 SLC47A1 seminal vesicle glandular cells Low Enhanced Q96FL8 +ENSG00000142494 SLC47A1 testis cells in seminiferous ducts Low Enhanced Q96FL8 +ENSG00000142494 SLC47A1 testis Leydig cells Low Enhanced Q96FL8 +ENSG00000142507 PSMB6 epididymis glandular cells Medium Supported P28072 +ENSG00000142507 PSMB6 prostate glandular cells Medium Supported P28072 +ENSG00000142507 PSMB6 seminal vesicle glandular cells High Supported P28072 +ENSG00000142507 PSMB6 testis cells in seminiferous ducts High Supported P28072 +ENSG00000142507 PSMB6 testis Leydig cells High Supported P28072 +ENSG00000142515 KLK3 prostate glandular cells High Enhanced P07288 +ENSG00000142583 SLC2A5 testis elongated or late spermatids High Enhanced P22732 +ENSG00000142583 SLC2A5 testis pachytene spermatocytes High Enhanced P22732 +ENSG00000142583 SLC2A5 testis round or early spermatids High Enhanced P22732 +ENSG00000142609 CFAP74 testis elongated or late spermatids High Enhanced Q9C0B2 +ENSG00000142621 FHAD1 testis elongated or late spermatids Medium Enhanced B1AJZ9 +ENSG00000142623 PADI1 testis cells in seminiferous ducts Medium Enhanced NA +ENSG00000142634 EFHD2 prostate glandular cells Low Enhanced Q96C19 +ENSG00000142634 EFHD2 testis cells in seminiferous ducts Medium Enhanced Q96C19 +ENSG00000142655 PEX14 epididymis glandular cells High Supported O75381 +ENSG00000142655 PEX14 prostate glandular cells High Supported O75381 +ENSG00000142655 PEX14 seminal vesicle glandular cells High Supported O75381 +ENSG00000142655 PEX14 testis cells in seminiferous ducts High Supported O75381 +ENSG00000142655 PEX14 testis Leydig cells Medium Supported O75381 +ENSG00000142657 PGD epididymis glandular cells Medium Enhanced P52209 +ENSG00000142657 PGD prostate glandular cells Medium Enhanced P52209 +ENSG00000142657 PGD seminal vesicle glandular cells Medium Enhanced P52209 +ENSG00000142657 PGD testis cells in seminiferous ducts High Enhanced P52209 +ENSG00000142657 PGD testis Leydig cells Low Enhanced P52209 +ENSG00000142684 ZNF593 epididymis glandular cells High Supported O00488 +ENSG00000142684 ZNF593 prostate glandular cells High Supported O00488 +ENSG00000142684 ZNF593 seminal vesicle glandular cells High Supported O00488 +ENSG00000142684 ZNF593 testis cells in seminiferous ducts High Supported O00488 +ENSG00000142684 ZNF593 testis Leydig cells High Supported O00488 +ENSG00000142765 SYTL1 epididymis glandular cells Medium Enhanced Q8IYJ3 +ENSG00000142765 SYTL1 prostate glandular cells High Enhanced Q8IYJ3 +ENSG00000142765 SYTL1 seminal vesicle glandular cells Medium Enhanced Q8IYJ3 +ENSG00000142765 SYTL1 testis cells in seminiferous ducts Medium Enhanced Q8IYJ3 +ENSG00000142765 SYTL1 testis Leydig cells Medium Enhanced Q8IYJ3 +ENSG00000142794 NBPF3 testis elongated or late spermatids High Supported Q9H094 +ENSG00000142794 NBPF3 testis round or early spermatids High Supported Q9H094 +ENSG00000142864 SERBP1 epididymis glandular cells Medium Enhanced Q8NC51 +ENSG00000142864 SERBP1 prostate glandular cells High Enhanced Q8NC51 +ENSG00000142864 SERBP1 seminal vesicle glandular cells Medium Enhanced Q8NC51 +ENSG00000142864 SERBP1 testis cells in seminiferous ducts Medium Enhanced Q8NC51 +ENSG00000142864 SERBP1 testis Leydig cells Medium Enhanced Q8NC51 +ENSG00000143006 DMRTB1 testis Leydig cells High Enhanced Q96MA1 +ENSG00000143006 DMRTB1 testis preleptotene spermatocytes High Enhanced Q96MA1 +ENSG00000143006 DMRTB1 testis sertoli cells High Enhanced Q96MA1 +ENSG00000143006 DMRTB1 testis spermatogonia High Enhanced Q96MA1 +ENSG00000143036 SLC44A3 epididymis glandular cells Medium Enhanced Q8N4M1 +ENSG00000143036 SLC44A3 prostate glandular cells Low Enhanced Q8N4M1 +ENSG00000143036 SLC44A3 seminal vesicle glandular cells Medium Enhanced Q8N4M1 +ENSG00000143036 SLC44A3 testis cells in seminiferous ducts Medium Enhanced Q8N4M1 +ENSG00000143036 SLC44A3 testis Leydig cells Medium Enhanced Q8N4M1 +ENSG00000143107 FNDC7 testis Leydig cells Low Enhanced Q5VTL7 +ENSG00000143107 FNDC7 testis sertoli cells High Enhanced Q5VTL7 +ENSG00000143153 ATP1B1 epididymis glandular cells High Enhanced P05026 +ENSG00000143153 ATP1B1 prostate glandular cells High Enhanced P05026 +ENSG00000143153 ATP1B1 seminal vesicle glandular cells High Enhanced P05026 +ENSG00000143153 ATP1B1 testis cells in seminiferous ducts High Enhanced P05026 +ENSG00000143153 ATP1B1 testis Leydig cells Low Enhanced P05026 +ENSG00000143190 POU2F1 epididymis glandular cells Medium Supported P14859 +ENSG00000143190 POU2F1 prostate glandular cells Medium Supported P14859 +ENSG00000143190 POU2F1 seminal vesicle glandular cells Medium Supported P14859 +ENSG00000143190 POU2F1 testis cells in seminiferous ducts Medium Supported P14859 +ENSG00000143190 POU2F1 testis Leydig cells Low Supported P14859 +ENSG00000143217 NECTIN4 epididymis glandular cells Low Enhanced Q96NY8 +ENSG00000143217 NECTIN4 prostate glandular cells Low Enhanced Q96NY8 +ENSG00000143217 NECTIN4 seminal vesicle glandular cells Low Enhanced Q96NY8 +ENSG00000143217 NECTIN4 testis Leydig cells Low Enhanced Q96NY8 +ENSG00000143222 UFC1 epididymis glandular cells Medium Enhanced Q9Y3C8 +ENSG00000143222 UFC1 prostate glandular cells Medium Enhanced Q9Y3C8 +ENSG00000143222 UFC1 seminal vesicle glandular cells Medium Enhanced Q9Y3C8 +ENSG00000143222 UFC1 testis cells in seminiferous ducts Low Enhanced Q9Y3C8 +ENSG00000143222 UFC1 testis Leydig cells Low Enhanced Q9Y3C8 +ENSG00000143294 PRCC epididymis glandular cells Low Supported Q92733 +ENSG00000143294 PRCC prostate glandular cells Medium Supported Q92733 +ENSG00000143294 PRCC seminal vesicle glandular cells Medium Supported Q92733 +ENSG00000143294 PRCC testis cells in seminiferous ducts Medium Supported Q92733 +ENSG00000143294 PRCC testis Leydig cells High Supported Q92733 +ENSG00000143318 CASQ1 testis cells in seminiferous ducts Low Enhanced P31415 +ENSG00000143318 CASQ1 testis Leydig cells Low Enhanced P31415 +ENSG00000143320 CRABP2 prostate glandular cells Low Supported P29373 +ENSG00000143321 HDGF epididymis glandular cells High Enhanced P51858 +ENSG00000143321 HDGF prostate glandular cells High Enhanced P51858 +ENSG00000143321 HDGF seminal vesicle glandular cells High Enhanced P51858 +ENSG00000143321 HDGF testis cells in seminiferous ducts Medium Enhanced P51858 +ENSG00000143321 HDGF testis Leydig cells High Enhanced P51858 +ENSG00000143324 XPR1 epididymis glandular cells Medium Enhanced Q9UBH6 +ENSG00000143324 XPR1 prostate glandular cells Medium Enhanced Q9UBH6 +ENSG00000143324 XPR1 seminal vesicle glandular cells Medium Enhanced Q9UBH6 +ENSG00000143324 XPR1 testis cells in seminiferous ducts High Enhanced Q9UBH6 +ENSG00000143324 XPR1 testis Leydig cells Medium Enhanced Q9UBH6 +ENSG00000143337 TOR1AIP1 epididymis glandular cells High Enhanced Q5JTV8 +ENSG00000143337 TOR1AIP1 prostate glandular cells High Enhanced Q5JTV8 +ENSG00000143337 TOR1AIP1 seminal vesicle glandular cells High Enhanced Q5JTV8 +ENSG00000143337 TOR1AIP1 testis cells in seminiferous ducts Medium Enhanced Q5JTV8 +ENSG00000143337 TOR1AIP1 testis Leydig cells High Enhanced Q5JTV8 +ENSG00000143369 ECM1 epididymis glandular cells High Enhanced Q16610 +ENSG00000143369 ECM1 seminal vesicle glandular cells Low Enhanced Q16610 +ENSG00000143375 CGN epididymis glandular cells Medium Enhanced Q9P2M7 +ENSG00000143375 CGN prostate glandular cells Medium Enhanced Q9P2M7 +ENSG00000143375 CGN seminal vesicle glandular cells Medium Enhanced Q9P2M7 +ENSG00000143375 CGN testis cells in seminiferous ducts Medium Enhanced Q9P2M7 +ENSG00000143390 RFX5 epididymis glandular cells High Supported P48382 +ENSG00000143390 RFX5 prostate glandular cells High Supported P48382 +ENSG00000143390 RFX5 seminal vesicle glandular cells High Supported P48382 +ENSG00000143390 RFX5 testis cells in seminiferous ducts High Supported P48382 +ENSG00000143390 RFX5 testis Leydig cells High Supported P48382 +ENSG00000143401 ANP32E epididymis glandular cells High Supported Q9BTT0 +ENSG00000143401 ANP32E prostate glandular cells High Supported Q9BTT0 +ENSG00000143401 ANP32E seminal vesicle glandular cells High Supported Q9BTT0 +ENSG00000143401 ANP32E testis cells in seminiferous ducts Medium Supported Q9BTT0 +ENSG00000143401 ANP32E testis Leydig cells High Supported Q9BTT0 +ENSG00000143412 ANXA9 epididymis glandular cells Medium Enhanced O76027 +ENSG00000143412 ANXA9 prostate glandular cells High Enhanced O76027 +ENSG00000143412 ANXA9 seminal vesicle glandular cells High Enhanced O76027 +ENSG00000143416 SELENBP1 epididymis glandular cells Medium Enhanced Q13228 +ENSG00000143416 SELENBP1 prostate glandular cells Low Enhanced Q13228 +ENSG00000143416 SELENBP1 seminal vesicle glandular cells Low Enhanced Q13228 +ENSG00000143416 SELENBP1 testis Leydig cells Medium Enhanced Q13228 +ENSG00000143437 ARNT epididymis glandular cells Low Enhanced P27540 +ENSG00000143437 ARNT prostate glandular cells Low Enhanced P27540 +ENSG00000143437 ARNT seminal vesicle glandular cells Low Enhanced P27540 +ENSG00000143437 ARNT testis cells in seminiferous ducts Low Enhanced P27540 +ENSG00000143437 ARNT testis Leydig cells Medium Enhanced P27540 +ENSG00000143442 POGZ epididymis glandular cells High Enhanced Q7Z3K3 +ENSG00000143442 POGZ prostate glandular cells Low Enhanced Q7Z3K3 +ENSG00000143442 POGZ seminal vesicle glandular cells Medium Enhanced Q7Z3K3 +ENSG00000143442 POGZ testis cells in seminiferous ducts High Enhanced Q7Z3K3 +ENSG00000143442 POGZ testis Leydig cells Medium Enhanced Q7Z3K3 +ENSG00000143443 C1orf56 testis elongated or late spermatids High Enhanced Q9BUN1 +ENSG00000143443 C1orf56 testis Leydig cells Low Enhanced Q9BUN1 +ENSG00000143443 C1orf56 testis round or early spermatids High Enhanced Q9BUN1 +ENSG00000143452 HORMAD1 testis pachytene spermatocytes High Enhanced Q86X24 +ENSG00000143452 HORMAD1 testis round or early spermatids High Enhanced Q86X24 +ENSG00000143512 HHIPL2 testis elongated or late spermatids Low Enhanced Q6UWX4 +ENSG00000143512 HHIPL2 testis spermatogonia Medium Enhanced Q6UWX4 +ENSG00000143514 TP53BP2 epididymis glandular cells Medium Supported Q13625 +ENSG00000143514 TP53BP2 prostate glandular cells Medium Supported Q13625 +ENSG00000143514 TP53BP2 seminal vesicle glandular cells Low Supported Q13625 +ENSG00000143514 TP53BP2 testis cells in seminiferous ducts High Supported Q13625 +ENSG00000143514 TP53BP2 testis Leydig cells Medium Supported Q13625 +ENSG00000143552 NUP210L testis elongated or late spermatids High Enhanced Q5VU65 +ENSG00000143552 NUP210L testis Leydig cells Low Enhanced Q5VU65 +ENSG00000143552 NUP210L testis pachytene spermatocytes High Enhanced Q5VU65 +ENSG00000143552 NUP210L testis round or early spermatids High Enhanced Q5VU65 +ENSG00000143556 S100A7 epididymis glandular cells Medium Enhanced P31151 +ENSG00000143578 CREB3L4 epididymis glandular cells Low Enhanced Q8TEY5 +ENSG00000143578 CREB3L4 prostate glandular cells High Enhanced Q8TEY5 +ENSG00000143578 CREB3L4 seminal vesicle glandular cells Medium Enhanced Q8TEY5 +ENSG00000143578 CREB3L4 testis cells in seminiferous ducts Medium Enhanced Q8TEY5 +ENSG00000143578 CREB3L4 testis Leydig cells Medium Enhanced Q8TEY5 +ENSG00000143621 ILF2 epididymis glandular cells High Supported Q12905 +ENSG00000143621 ILF2 prostate glandular cells High Supported Q12905 +ENSG00000143621 ILF2 seminal vesicle glandular cells High Supported Q12905 +ENSG00000143621 ILF2 testis cells in seminiferous ducts High Supported Q12905 +ENSG00000143621 ILF2 testis Leydig cells High Supported Q12905 +ENSG00000143627 PKLR epididymis glandular cells Low Enhanced NA +ENSG00000143633 C1orf131 epididymis glandular cells Medium Enhanced Q8NDD1 +ENSG00000143633 C1orf131 prostate glandular cells Medium Enhanced Q8NDD1 +ENSG00000143633 C1orf131 seminal vesicle glandular cells Medium Enhanced Q8NDD1 +ENSG00000143633 C1orf131 testis cells in seminiferous ducts Medium Enhanced Q8NDD1 +ENSG00000143633 C1orf131 testis Leydig cells Medium Enhanced Q8NDD1 +ENSG00000143641 GALNT2 epididymis glandular cells Medium Supported Q10471 +ENSG00000143641 GALNT2 prostate glandular cells Medium Supported Q10471 +ENSG00000143641 GALNT2 seminal vesicle glandular cells Medium Supported Q10471 +ENSG00000143641 GALNT2 testis cells in seminiferous ducts Low Supported Q10471 +ENSG00000143641 GALNT2 testis Leydig cells Medium Supported Q10471 +ENSG00000143740 SNAP47 epididymis glandular cells Medium Enhanced Q5SQN1 +ENSG00000143740 SNAP47 prostate glandular cells High Enhanced Q5SQN1 +ENSG00000143740 SNAP47 seminal vesicle glandular cells High Enhanced Q5SQN1 +ENSG00000143740 SNAP47 testis cells in seminiferous ducts Medium Enhanced Q5SQN1 +ENSG00000143740 SNAP47 testis Leydig cells High Enhanced Q5SQN1 +ENSG00000143748 NVL epididymis glandular cells Low Enhanced O15381 +ENSG00000143748 NVL prostate glandular cells Medium Enhanced O15381 +ENSG00000143748 NVL seminal vesicle glandular cells Medium Enhanced O15381 +ENSG00000143799 PARP1 epididymis glandular cells Medium Supported P09874 +ENSG00000143799 PARP1 prostate glandular cells Medium Supported P09874 +ENSG00000143799 PARP1 seminal vesicle glandular cells Medium Supported P09874 +ENSG00000143799 PARP1 testis cells in seminiferous ducts High Supported P09874 +ENSG00000143799 PARP1 testis Leydig cells Medium Supported P09874 +ENSG00000143815 LBR epididymis glandular cells Low Enhanced Q14739 +ENSG00000143815 LBR testis cells in seminiferous ducts Medium Enhanced Q14739 +ENSG00000143819 EPHX1 testis Leydig cells High Enhanced P07099 +ENSG00000143845 ETNK2 prostate glandular cells Low Enhanced Q9NVF9 +ENSG00000143845 ETNK2 seminal vesicle glandular cells Low Enhanced Q9NVF9 +ENSG00000143845 ETNK2 testis cells in seminiferous ducts High Enhanced Q9NVF9 +ENSG00000143845 ETNK2 testis Leydig cells High Enhanced Q9NVF9 +ENSG00000143870 PDIA6 epididymis glandular cells High Enhanced Q15084 +ENSG00000143870 PDIA6 prostate glandular cells Medium Enhanced Q15084 +ENSG00000143870 PDIA6 seminal vesicle glandular cells Medium Enhanced Q15084 +ENSG00000143870 PDIA6 testis cells in seminiferous ducts Medium Enhanced Q15084 +ENSG00000143870 PDIA6 testis Leydig cells Medium Enhanced Q15084 +ENSG00000143891 GALM epididymis glandular cells Low Enhanced Q96C23 +ENSG00000143891 GALM seminal vesicle glandular cells Low Enhanced Q96C23 +ENSG00000143891 GALM testis Leydig cells Low Enhanced Q96C23 +ENSG00000143924 EML4 epididymis glandular cells Medium Enhanced Q9HC35 +ENSG00000143924 EML4 prostate glandular cells High Enhanced Q9HC35 +ENSG00000143924 EML4 seminal vesicle glandular cells Medium Enhanced Q9HC35 +ENSG00000143924 EML4 testis cells in seminiferous ducts Medium Enhanced Q9HC35 +ENSG00000143924 EML4 testis Leydig cells Medium Enhanced Q9HC35 +ENSG00000143947 RPS27A epididymis glandular cells Medium Supported P62979 +ENSG00000143947 RPS27A prostate glandular cells High Supported P62979 +ENSG00000143947 RPS27A seminal vesicle glandular cells Medium Supported P62979 +ENSG00000143947 RPS27A testis cells in seminiferous ducts High Supported P62979 +ENSG00000143947 RPS27A testis Leydig cells Medium Supported P62979 +ENSG00000143977 SNRPG epididymis glandular cells Medium Enhanced P62308 +ENSG00000143977 SNRPG prostate glandular cells High Enhanced P62308 +ENSG00000143977 SNRPG seminal vesicle glandular cells Medium Enhanced P62308 +ENSG00000143977 SNRPG testis cells in seminiferous ducts Medium Enhanced P62308 +ENSG00000143977 SNRPG testis Leydig cells Medium Enhanced P62308 +ENSG00000144366 GULP1 epididymis glandular cells Medium Enhanced Q9UBP9 +ENSG00000144366 GULP1 prostate glandular cells Low Enhanced Q9UBP9 +ENSG00000144366 GULP1 testis cells in seminiferous ducts Medium Enhanced Q9UBP9 +ENSG00000144366 GULP1 testis Leydig cells Low Enhanced Q9UBP9 +ENSG00000144381 HSPD1 epididymis glandular cells Medium Supported P10809 +ENSG00000144381 HSPD1 prostate glandular cells Medium Supported P10809 +ENSG00000144381 HSPD1 testis cells in seminiferous ducts Low Supported P10809 +ENSG00000144381 HSPD1 testis Leydig cells Low Supported P10809 +ENSG00000144597 EAF1 epididymis glandular cells High Enhanced Q96JC9 +ENSG00000144597 EAF1 prostate glandular cells Medium Enhanced Q96JC9 +ENSG00000144597 EAF1 seminal vesicle glandular cells High Enhanced Q96JC9 +ENSG00000144597 EAF1 testis cells in seminiferous ducts High Enhanced Q96JC9 +ENSG00000144597 EAF1 testis Leydig cells Medium Enhanced Q96JC9 +ENSG00000144648 ACKR2 testis cells in seminiferous ducts Low Enhanced O00590 +ENSG00000144648 ACKR2 testis Leydig cells Low Enhanced O00590 +ENSG00000144674 GOLGA4 epididymis glandular cells High Supported Q13439 +ENSG00000144674 GOLGA4 prostate glandular cells High Supported Q13439 +ENSG00000144674 GOLGA4 seminal vesicle glandular cells High Supported Q13439 +ENSG00000144674 GOLGA4 testis cells in seminiferous ducts High Supported Q13439 +ENSG00000144674 GOLGA4 testis Leydig cells Medium Supported Q13439 +ENSG00000144713 RPL32 epididymis glandular cells Low Enhanced P62910 +ENSG00000144713 RPL32 prostate glandular cells Low Enhanced P62910 +ENSG00000144713 RPL32 seminal vesicle glandular cells Medium Enhanced P62910 +ENSG00000144713 RPL32 testis cells in seminiferous ducts Low Enhanced P62910 +ENSG00000144713 RPL32 testis Leydig cells Medium Enhanced P62910 +ENSG00000144741 SLC25A26 epididymis glandular cells Medium Enhanced NA +ENSG00000144741 SLC25A26 prostate glandular cells Medium Enhanced NA +ENSG00000144741 SLC25A26 seminal vesicle glandular cells Medium Enhanced NA +ENSG00000144741 SLC25A26 testis cells in seminiferous ducts High Enhanced NA +ENSG00000144741 SLC25A26 testis Leydig cells Medium Enhanced NA +ENSG00000144744 UBA3 epididymis glandular cells Medium Enhanced Q8TBC4 +ENSG00000144744 UBA3 prostate glandular cells Medium Enhanced Q8TBC4 +ENSG00000144744 UBA3 seminal vesicle glandular cells Medium Enhanced Q8TBC4 +ENSG00000144744 UBA3 testis cells in seminiferous ducts High Enhanced Q8TBC4 +ENSG00000144744 UBA3 testis Leydig cells High Enhanced Q8TBC4 +ENSG00000144746 ARL6IP5 epididymis glandular cells Medium Supported O75915 +ENSG00000144746 ARL6IP5 prostate glandular cells Medium Supported O75915 +ENSG00000144746 ARL6IP5 seminal vesicle glandular cells Medium Supported O75915 +ENSG00000144746 ARL6IP5 testis cells in seminiferous ducts High Supported O75915 +ENSG00000144746 ARL6IP5 testis Leydig cells High Supported O75915 +ENSG00000144827 ABHD10 epididymis glandular cells High Supported Q9NUJ1 +ENSG00000144827 ABHD10 prostate glandular cells Medium Supported Q9NUJ1 +ENSG00000144827 ABHD10 seminal vesicle glandular cells High Supported Q9NUJ1 +ENSG00000144827 ABHD10 testis cells in seminiferous ducts High Supported Q9NUJ1 +ENSG00000144827 ABHD10 testis Leydig cells High Supported Q9NUJ1 +ENSG00000144848 ATG3 epididymis glandular cells Medium Enhanced Q9NT62 +ENSG00000144848 ATG3 prostate glandular cells Medium Enhanced Q9NT62 +ENSG00000144848 ATG3 seminal vesicle glandular cells Medium Enhanced Q9NT62 +ENSG00000144848 ATG3 testis cells in seminiferous ducts High Enhanced Q9NT62 +ENSG00000144848 ATG3 testis Leydig cells High Enhanced Q9NT62 +ENSG00000144908 ALDH1L1 epididymis glandular cells Low Enhanced O75891 +ENSG00000144908 ALDH1L1 prostate glandular cells Low Enhanced O75891 +ENSG00000144908 ALDH1L1 seminal vesicle glandular cells Low Enhanced O75891 +ENSG00000144908 ALDH1L1 testis cells in seminiferous ducts Low Enhanced O75891 +ENSG00000144908 ALDH1L1 testis Leydig cells Low Enhanced O75891 +ENSG00000144935 TRPC1 epididymis glandular cells High Supported P48995 +ENSG00000144935 TRPC1 prostate glandular cells High Supported P48995 +ENSG00000144935 TRPC1 seminal vesicle glandular cells Medium Supported P48995 +ENSG00000144935 TRPC1 testis cells in seminiferous ducts Medium Supported P48995 +ENSG00000144935 TRPC1 testis Leydig cells Medium Supported P48995 +ENSG00000144959 NCEH1 prostate glandular cells Low Supported Q6PIU2 +ENSG00000144959 NCEH1 testis Leydig cells Low Supported Q6PIU2 +ENSG00000144962 SPATA16 testis pachytene spermatocytes Low Enhanced Q9BXB7 +ENSG00000144962 SPATA16 testis preleptotene spermatocytes Medium Enhanced Q9BXB7 +ENSG00000144962 SPATA16 testis round or early spermatids Low Enhanced Q9BXB7 +ENSG00000144962 SPATA16 testis spermatogonia Medium Enhanced Q9BXB7 +ENSG00000145020 AMT epididymis glandular cells High Supported P48728 +ENSG00000145020 AMT prostate glandular cells High Supported P48728 +ENSG00000145020 AMT seminal vesicle glandular cells High Supported P48728 +ENSG00000145020 AMT testis cells in seminiferous ducts High Supported P48728 +ENSG00000145020 AMT testis Leydig cells High Supported P48728 +ENSG00000145075 CCDC39 testis cells in seminiferous ducts Medium Enhanced Q9UFE4 +ENSG00000145088 EAF2 seminal vesicle glandular cells Low Enhanced Q96CJ1 +ENSG00000145194 ECE2 epididymis glandular cells Medium Enhanced P0DPD6 +ENSG00000145194 ECE2 prostate glandular cells Medium Enhanced P0DPD6 +ENSG00000145194 ECE2 testis Leydig cells Medium Enhanced P0DPD6 +ENSG00000145198 VWA5B2 epididymis glandular cells Medium Enhanced Q8N398 +ENSG00000145198 VWA5B2 prostate glandular cells Low Enhanced Q8N398 +ENSG00000145198 VWA5B2 seminal vesicle glandular cells Medium Enhanced Q8N398 +ENSG00000145198 VWA5B2 testis cells in seminiferous ducts Medium Enhanced Q8N398 +ENSG00000145198 VWA5B2 testis Leydig cells Medium Enhanced Q8N398 +ENSG00000145216 FIP1L1 epididymis glandular cells High Enhanced Q6UN15 +ENSG00000145216 FIP1L1 prostate glandular cells Medium Enhanced Q6UN15 +ENSG00000145216 FIP1L1 seminal vesicle glandular cells Medium Enhanced Q6UN15 +ENSG00000145216 FIP1L1 testis cells in seminiferous ducts High Enhanced Q6UN15 +ENSG00000145216 FIP1L1 testis Leydig cells Medium Enhanced Q6UN15 +ENSG00000145220 LYAR testis cells in seminiferous ducts High Enhanced Q9NX58 +ENSG00000145247 OCIAD2 epididymis glandular cells Low Enhanced Q56VL3 +ENSG00000145247 OCIAD2 prostate glandular cells Low Enhanced Q56VL3 +ENSG00000145283 SLC10A6 prostate glandular cells Medium Enhanced Q3KNW5 +ENSG00000145287 PLAC8 epididymis glandular cells Medium Supported Q9NZF1 +ENSG00000145287 PLAC8 prostate glandular cells High Supported Q9NZF1 +ENSG00000145287 PLAC8 seminal vesicle glandular cells Medium Supported Q9NZF1 +ENSG00000145293 ENOPH1 epididymis glandular cells Medium Enhanced Q9UHY7 +ENSG00000145293 ENOPH1 prostate glandular cells Medium Enhanced Q9UHY7 +ENSG00000145293 ENOPH1 seminal vesicle glandular cells Low Enhanced Q9UHY7 +ENSG00000145293 ENOPH1 testis Leydig cells Medium Enhanced Q9UHY7 +ENSG00000145309 CABS1 testis elongated or late spermatids High Enhanced Q96KC9 +ENSG00000145309 CABS1 testis pachytene spermatocytes Low Enhanced Q96KC9 +ENSG00000145309 CABS1 testis round or early spermatids Medium Enhanced Q96KC9 +ENSG00000145321 GC prostate glandular cells Medium Supported P02774 +ENSG00000145321 GC seminal vesicle glandular cells Low Supported P02774 +ENSG00000145321 GC testis cells in seminiferous ducts Low Supported P02774 +ENSG00000145321 GC testis Leydig cells Medium Supported P02774 +ENSG00000145335 SNCA testis Leydig cells Low Enhanced P37840 +ENSG00000145362 ANK2 testis Leydig cells Low Enhanced Q01484 +ENSG00000145386 CCNA2 testis cells in seminiferous ducts Medium Enhanced P20248 +ENSG00000145388 METTL14 epididymis glandular cells Medium Supported Q9HCE5 +ENSG00000145388 METTL14 prostate glandular cells Medium Supported Q9HCE5 +ENSG00000145388 METTL14 seminal vesicle glandular cells Medium Supported Q9HCE5 +ENSG00000145388 METTL14 testis cells in seminiferous ducts High Supported Q9HCE5 +ENSG00000145388 METTL14 testis Leydig cells Medium Supported Q9HCE5 +ENSG00000145439 CBR4 epididymis glandular cells Medium Supported Q8N4T8 +ENSG00000145439 CBR4 prostate glandular cells Medium Supported Q8N4T8 +ENSG00000145439 CBR4 seminal vesicle glandular cells Medium Supported Q8N4T8 +ENSG00000145439 CBR4 testis cells in seminiferous ducts Medium Supported Q8N4T8 +ENSG00000145439 CBR4 testis Leydig cells High Supported Q8N4T8 +ENSG00000145491 ROPN1L testis elongated or late spermatids High Enhanced Q96C74 +ENSG00000145491 ROPN1L testis pachytene spermatocytes Low Enhanced Q96C74 +ENSG00000145491 ROPN1L testis round or early spermatids Medium Enhanced Q96C74 +ENSG00000145494 NDUFS6 prostate glandular cells Medium Supported O75380 +ENSG00000145494 NDUFS6 seminal vesicle glandular cells High Supported O75380 +ENSG00000145494 NDUFS6 testis cells in seminiferous ducts High Supported O75380 +ENSG00000145494 NDUFS6 testis Leydig cells High Supported O75380 +ENSG00000145555 MYO10 epididymis glandular cells Medium Enhanced Q9HD67 +ENSG00000145555 MYO10 prostate glandular cells Medium Enhanced Q9HD67 +ENSG00000145555 MYO10 seminal vesicle glandular cells Medium Enhanced Q9HD67 +ENSG00000145555 MYO10 testis cells in seminiferous ducts Low Enhanced Q9HD67 +ENSG00000145555 MYO10 testis Leydig cells Low Enhanced Q9HD67 +ENSG00000145700 ANKRD31 testis elongated or late spermatids Medium Enhanced Q8N7Z5 +ENSG00000145700 ANKRD31 testis Leydig cells High Enhanced Q8N7Z5 +ENSG00000145700 ANKRD31 testis pachytene spermatocytes Medium Enhanced Q8N7Z5 +ENSG00000145700 ANKRD31 testis preleptotene spermatocytes Medium Enhanced Q8N7Z5 +ENSG00000145700 ANKRD31 testis round or early spermatids Medium Enhanced Q8N7Z5 +ENSG00000145700 ANKRD31 testis spermatogonia Low Enhanced Q8N7Z5 +ENSG00000145715 RASA1 epididymis glandular cells Low Enhanced P20936 +ENSG00000145730 PAM epididymis glandular cells High Enhanced P19021 +ENSG00000145817 YIPF5 epididymis glandular cells High Enhanced Q969M3 +ENSG00000145817 YIPF5 prostate glandular cells Medium Enhanced Q969M3 +ENSG00000145817 YIPF5 seminal vesicle glandular cells High Enhanced Q969M3 +ENSG00000145817 YIPF5 testis cells in seminiferous ducts Medium Enhanced Q969M3 +ENSG00000145817 YIPF5 testis Leydig cells High Enhanced Q969M3 +ENSG00000145826 LECT2 testis Leydig cells High Enhanced O14960 +ENSG00000145833 DDX46 epididymis glandular cells High Supported Q7L014 +ENSG00000145833 DDX46 prostate glandular cells High Supported Q7L014 +ENSG00000145833 DDX46 seminal vesicle glandular cells Medium Supported Q7L014 +ENSG00000145833 DDX46 testis cells in seminiferous ducts High Supported Q7L014 +ENSG00000145833 DDX46 testis Leydig cells High Supported Q7L014 +ENSG00000145907 G3BP1 epididymis glandular cells Medium Supported Q13283 +ENSG00000145907 G3BP1 prostate glandular cells Low Supported Q13283 +ENSG00000145907 G3BP1 seminal vesicle glandular cells Medium Supported Q13283 +ENSG00000145907 G3BP1 testis cells in seminiferous ducts High Supported Q13283 +ENSG00000145907 G3BP1 testis Leydig cells Low Supported Q13283 +ENSG00000145912 NHP2 epididymis glandular cells Medium Enhanced Q9NX24 +ENSG00000145912 NHP2 seminal vesicle glandular cells Medium Enhanced Q9NX24 +ENSG00000145912 NHP2 testis cells in seminiferous ducts Medium Enhanced Q9NX24 +ENSG00000145912 NHP2 testis Leydig cells Low Enhanced Q9NX24 +ENSG00000146038 DCDC2 epididymis glandular cells Medium Enhanced Q9UHG0 +ENSG00000146038 DCDC2 prostate glandular cells Low Enhanced Q9UHG0 +ENSG00000146038 DCDC2 seminal vesicle glandular cells Medium Enhanced Q9UHG0 +ENSG00000146038 DCDC2 testis cells in seminiferous ducts Low Enhanced Q9UHG0 +ENSG00000146047 HIST1H2BA testis elongated or late spermatids High Enhanced Q96A08 +ENSG00000146047 HIST1H2BA testis Leydig cells Medium Enhanced Q96A08 +ENSG00000146047 HIST1H2BA testis pachytene spermatocytes High Enhanced Q96A08 +ENSG00000146047 HIST1H2BA testis preleptotene spermatocytes High Enhanced Q96A08 +ENSG00000146047 HIST1H2BA testis spermatogonia High Enhanced Q96A08 +ENSG00000146085 MUT epididymis glandular cells Medium Enhanced P22033 +ENSG00000146085 MUT prostate glandular cells Medium Enhanced P22033 +ENSG00000146085 MUT seminal vesicle glandular cells Medium Enhanced P22033 +ENSG00000146085 MUT testis cells in seminiferous ducts Medium Enhanced P22033 +ENSG00000146085 MUT testis Leydig cells Medium Enhanced P22033 +ENSG00000146232 NFKBIE epididymis glandular cells Medium Supported O00221 +ENSG00000146232 NFKBIE prostate glandular cells Medium Supported O00221 +ENSG00000146232 NFKBIE seminal vesicle glandular cells Medium Supported O00221 +ENSG00000146232 NFKBIE testis cells in seminiferous ducts Medium Supported O00221 +ENSG00000146232 NFKBIE testis Leydig cells Medium Supported O00221 +ENSG00000146242 TPBG epididymis glandular cells High Enhanced NA +ENSG00000146242 TPBG prostate glandular cells Medium Enhanced NA +ENSG00000146242 TPBG seminal vesicle glandular cells High Enhanced NA +ENSG00000146242 TPBG testis cells in seminiferous ducts Low Enhanced NA +ENSG00000146242 TPBG testis Leydig cells Medium Enhanced NA +ENSG00000146386 ABRACL epididymis glandular cells High Enhanced Q9P1F3 +ENSG00000146386 ABRACL prostate glandular cells Low Enhanced Q9P1F3 +ENSG00000146386 ABRACL seminal vesicle glandular cells Medium Enhanced Q9P1F3 +ENSG00000146386 ABRACL testis cells in seminiferous ducts High Enhanced Q9P1F3 +ENSG00000146386 ABRACL testis Leydig cells Low Enhanced Q9P1F3 +ENSG00000146457 WTAP epididymis glandular cells High Supported Q15007 +ENSG00000146457 WTAP prostate glandular cells Medium Supported Q15007 +ENSG00000146457 WTAP seminal vesicle glandular cells Medium Supported Q15007 +ENSG00000146457 WTAP testis cells in seminiferous ducts High Supported Q15007 +ENSG00000146457 WTAP testis Leydig cells Medium Supported Q15007 +ENSG00000146469 VIP epididymis glandular cells Low Supported P01282 +ENSG00000146469 VIP prostate glandular cells Low Supported P01282 +ENSG00000146469 VIP seminal vesicle glandular cells Low Supported P01282 +ENSG00000146469 VIP testis cells in seminiferous ducts Medium Supported P01282 +ENSG00000146469 VIP testis Leydig cells Medium Supported P01282 +ENSG00000146648 EGFR testis Leydig cells Low Enhanced P00533 +ENSG00000146701 MDH2 epididymis glandular cells Medium Enhanced P40926 +ENSG00000146701 MDH2 prostate glandular cells High Enhanced P40926 +ENSG00000146701 MDH2 seminal vesicle glandular cells High Enhanced P40926 +ENSG00000146701 MDH2 testis cells in seminiferous ducts Medium Enhanced P40926 +ENSG00000146701 MDH2 testis Leydig cells High Enhanced P40926 +ENSG00000146729 GBAS epididymis glandular cells Medium Enhanced O75323 +ENSG00000146729 GBAS prostate glandular cells High Enhanced O75323 +ENSG00000146729 GBAS seminal vesicle glandular cells High Enhanced O75323 +ENSG00000146729 GBAS testis cells in seminiferous ducts Medium Enhanced O75323 +ENSG00000146729 GBAS testis Leydig cells High Enhanced O75323 +ENSG00000146731 CCT6A epididymis glandular cells Medium Supported P40227 +ENSG00000146731 CCT6A prostate glandular cells Medium Supported P40227 +ENSG00000146731 CCT6A seminal vesicle glandular cells High Supported P40227 +ENSG00000146731 CCT6A testis cells in seminiferous ducts High Supported P40227 +ENSG00000146731 CCT6A testis Leydig cells Medium Supported P40227 +ENSG00000146830 GIGYF1 epididymis glandular cells High Enhanced O75420 +ENSG00000146830 GIGYF1 prostate glandular cells Medium Enhanced O75420 +ENSG00000146830 GIGYF1 seminal vesicle glandular cells Medium Enhanced O75420 +ENSG00000146830 GIGYF1 testis cells in seminiferous ducts High Enhanced O75420 +ENSG00000146830 GIGYF1 testis Leydig cells High Enhanced O75420 +ENSG00000146834 MEPCE epididymis glandular cells Medium Supported Q7L2J0 +ENSG00000146834 MEPCE prostate glandular cells High Supported Q7L2J0 +ENSG00000146834 MEPCE seminal vesicle glandular cells High Supported Q7L2J0 +ENSG00000146834 MEPCE testis cells in seminiferous ducts High Supported Q7L2J0 +ENSG00000146834 MEPCE testis Leydig cells High Supported Q7L2J0 +ENSG00000147044 CASK epididymis glandular cells Medium Enhanced O14936 +ENSG00000147044 CASK prostate glandular cells Medium Enhanced O14936 +ENSG00000147044 CASK seminal vesicle glandular cells Low Enhanced O14936 +ENSG00000147044 CASK testis cells in seminiferous ducts Low Enhanced O14936 +ENSG00000147044 CASK testis Leydig cells Medium Enhanced O14936 +ENSG00000147050 KDM6A epididymis glandular cells Low Enhanced O15550 +ENSG00000147050 KDM6A prostate glandular cells Low Enhanced O15550 +ENSG00000147050 KDM6A testis Leydig cells Low Enhanced O15550 +ENSG00000147065 MSN epididymis glandular cells Medium Enhanced P26038 +ENSG00000147065 MSN prostate glandular cells Low Enhanced P26038 +ENSG00000147065 MSN seminal vesicle glandular cells Low Enhanced P26038 +ENSG00000147065 MSN testis cells in seminiferous ducts Low Enhanced P26038 +ENSG00000147065 MSN testis Leydig cells Medium Enhanced P26038 +ENSG00000147081 AKAP4 testis elongated or late spermatids High Enhanced Q5JQC9 +ENSG00000147081 AKAP4 testis pachytene spermatocytes Low Enhanced Q5JQC9 +ENSG00000147081 AKAP4 testis preleptotene spermatocytes Low Enhanced Q5JQC9 +ENSG00000147081 AKAP4 testis round or early spermatids Low Enhanced Q5JQC9 +ENSG00000147082 CCNB3 testis cells in seminiferous ducts Medium Enhanced Q8WWL7 +ENSG00000147082 CCNB3 testis Leydig cells Low Enhanced Q8WWL7 +ENSG00000147099 HDAC8 epididymis glandular cells Medium Supported Q9BY41 +ENSG00000147099 HDAC8 prostate glandular cells Medium Supported Q9BY41 +ENSG00000147099 HDAC8 seminal vesicle glandular cells Medium Supported Q9BY41 +ENSG00000147099 HDAC8 testis cells in seminiferous ducts Low Supported Q9BY41 +ENSG00000147099 HDAC8 testis Leydig cells Medium Supported Q9BY41 +ENSG00000147123 NDUFB11 epididymis glandular cells Medium Supported Q9NX14 +ENSG00000147123 NDUFB11 prostate glandular cells Medium Supported Q9NX14 +ENSG00000147123 NDUFB11 seminal vesicle glandular cells Medium Supported Q9NX14 +ENSG00000147123 NDUFB11 testis cells in seminiferous ducts Medium Supported Q9NX14 +ENSG00000147123 NDUFB11 testis Leydig cells Medium Supported Q9NX14 +ENSG00000147124 ZNF41 epididymis glandular cells Medium Enhanced P51814 +ENSG00000147124 ZNF41 prostate glandular cells Medium Enhanced P51814 +ENSG00000147124 ZNF41 seminal vesicle glandular cells Low Enhanced P51814 +ENSG00000147124 ZNF41 testis cells in seminiferous ducts Medium Enhanced P51814 +ENSG00000147124 ZNF41 testis Leydig cells Medium Enhanced P51814 +ENSG00000147133 TAF1 epididymis glandular cells High Supported P21675 +ENSG00000147133 TAF1 prostate glandular cells High Supported P21675 +ENSG00000147133 TAF1 seminal vesicle glandular cells High Supported P21675 +ENSG00000147133 TAF1 testis cells in seminiferous ducts High Supported P21675 +ENSG00000147133 TAF1 testis Leydig cells High Supported P21675 +ENSG00000147140 NONO epididymis glandular cells High Enhanced Q15233 +ENSG00000147140 NONO prostate glandular cells High Enhanced Q15233 +ENSG00000147140 NONO seminal vesicle glandular cells High Enhanced Q15233 +ENSG00000147140 NONO testis cells in seminiferous ducts High Enhanced Q15233 +ENSG00000147140 NONO testis Leydig cells High Enhanced Q15233 +ENSG00000147174 GCNA testis elongated or late spermatids Medium Enhanced Q96QF7 +ENSG00000147174 GCNA testis Leydig cells Low Enhanced Q96QF7 +ENSG00000147174 GCNA testis pachytene spermatocytes Medium Enhanced Q96QF7 +ENSG00000147174 GCNA testis preleptotene spermatocytes High Enhanced Q96QF7 +ENSG00000147174 GCNA testis round or early spermatids Low Enhanced Q96QF7 +ENSG00000147174 GCNA testis spermatogonia High Enhanced Q96QF7 +ENSG00000147180 ZNF711 epididymis glandular cells Medium Enhanced Q9Y462 +ENSG00000147180 ZNF711 prostate glandular cells Medium Enhanced Q9Y462 +ENSG00000147180 ZNF711 testis elongated or late spermatids Low Enhanced Q9Y462 +ENSG00000147180 ZNF711 testis Leydig cells Medium Enhanced Q9Y462 +ENSG00000147180 ZNF711 testis pachytene spermatocytes Medium Enhanced Q9Y462 +ENSG00000147180 ZNF711 testis peritubular cells Low Enhanced Q9Y462 +ENSG00000147180 ZNF711 testis preleptotene spermatocytes High Enhanced Q9Y462 +ENSG00000147180 ZNF711 testis round or early spermatids Low Enhanced Q9Y462 +ENSG00000147180 ZNF711 testis sertoli cells High Enhanced Q9Y462 +ENSG00000147180 ZNF711 testis spermatogonia Medium Enhanced Q9Y462 +ENSG00000147202 DIAPH2 epididymis glandular cells Medium Enhanced O60879 +ENSG00000147202 DIAPH2 prostate glandular cells Medium Enhanced O60879 +ENSG00000147202 DIAPH2 seminal vesicle glandular cells Medium Enhanced O60879 +ENSG00000147202 DIAPH2 testis cells in seminiferous ducts High Enhanced O60879 +ENSG00000147202 DIAPH2 testis Leydig cells Low Enhanced O60879 +ENSG00000147255 IGSF1 testis cells in seminiferous ducts Low Enhanced Q8N6C5 +ENSG00000147274 RBMX epididymis glandular cells High Supported P38159 +ENSG00000147274 RBMX prostate glandular cells Medium Supported P38159 +ENSG00000147274 RBMX seminal vesicle glandular cells Medium Supported P38159 +ENSG00000147274 RBMX testis cells in seminiferous ducts High Supported P38159 +ENSG00000147274 RBMX testis Leydig cells High Supported P38159 +ENSG00000147316 MCPH1 epididymis glandular cells High Supported Q8NEM0 +ENSG00000147316 MCPH1 prostate glandular cells Medium Supported Q8NEM0 +ENSG00000147316 MCPH1 seminal vesicle glandular cells Medium Supported Q8NEM0 +ENSG00000147316 MCPH1 testis cells in seminiferous ducts High Supported Q8NEM0 +ENSG00000147316 MCPH1 testis Leydig cells High Supported Q8NEM0 +ENSG00000147378 FATE1 testis Leydig cells Low Enhanced Q969F0 +ENSG00000147378 FATE1 testis sertoli cells Medium Enhanced Q969F0 +ENSG00000147381 MAGEA4 testis cells in seminiferous ducts High Enhanced P43358 +ENSG00000147381 MAGEA4 testis Leydig cells Medium Enhanced P43358 +ENSG00000147383 NSDHL epididymis glandular cells High Enhanced Q15738 +ENSG00000147383 NSDHL prostate glandular cells Low Enhanced Q15738 +ENSG00000147383 NSDHL seminal vesicle glandular cells Medium Enhanced Q15738 +ENSG00000147383 NSDHL testis cells in seminiferous ducts Medium Enhanced Q15738 +ENSG00000147383 NSDHL testis Leydig cells Medium Enhanced Q15738 +ENSG00000147394 ZNF185 epididymis glandular cells High Enhanced O15231 +ENSG00000147394 ZNF185 seminal vesicle glandular cells High Enhanced O15231 +ENSG00000147403 RPL10 epididymis glandular cells High Enhanced P27635 +ENSG00000147403 RPL10 prostate glandular cells High Enhanced P27635 +ENSG00000147403 RPL10 seminal vesicle glandular cells High Enhanced P27635 +ENSG00000147403 RPL10 testis cells in seminiferous ducts Medium Enhanced P27635 +ENSG00000147403 RPL10 testis Leydig cells High Enhanced P27635 +ENSG00000147416 ATP6V1B2 epididymis glandular cells Medium Enhanced P21281 +ENSG00000147416 ATP6V1B2 prostate glandular cells Medium Enhanced P21281 +ENSG00000147416 ATP6V1B2 seminal vesicle glandular cells Medium Enhanced P21281 +ENSG00000147416 ATP6V1B2 testis cells in seminiferous ducts Medium Enhanced P21281 +ENSG00000147416 ATP6V1B2 testis Leydig cells High Enhanced P21281 +ENSG00000147421 HMBOX1 seminal vesicle glandular cells Low Enhanced Q6NT76 +ENSG00000147421 HMBOX1 testis cells in seminiferous ducts Low Enhanced Q6NT76 +ENSG00000147421 HMBOX1 testis Leydig cells Medium Enhanced Q6NT76 +ENSG00000147432 CHRNB3 testis cells in seminiferous ducts Low Enhanced Q05901 +ENSG00000147437 GNRH1 epididymis glandular cells Medium Supported P01148 +ENSG00000147437 GNRH1 prostate glandular cells Low Supported P01148 +ENSG00000147437 GNRH1 seminal vesicle glandular cells Low Supported P01148 +ENSG00000147437 GNRH1 testis cells in seminiferous ducts Low Supported P01148 +ENSG00000147437 GNRH1 testis Leydig cells Low Supported P01148 +ENSG00000147465 STAR testis Leydig cells High Enhanced P49675 +ENSG00000147475 ERLIN2 epididymis glandular cells High Enhanced O94905 +ENSG00000147475 ERLIN2 prostate glandular cells Medium Enhanced O94905 +ENSG00000147475 ERLIN2 seminal vesicle glandular cells Medium Enhanced O94905 +ENSG00000147475 ERLIN2 testis cells in seminiferous ducts High Enhanced O94905 +ENSG00000147475 ERLIN2 testis Leydig cells High Enhanced O94905 +ENSG00000147576 ADHFE1 prostate glandular cells Low Enhanced Q8IWW8 +ENSG00000147649 MTDH epididymis glandular cells High Supported Q86UE4 +ENSG00000147649 MTDH prostate glandular cells High Supported Q86UE4 +ENSG00000147649 MTDH seminal vesicle glandular cells High Supported Q86UE4 +ENSG00000147649 MTDH testis cells in seminiferous ducts High Supported Q86UE4 +ENSG00000147649 MTDH testis Leydig cells High Supported Q86UE4 +ENSG00000147654 EBAG9 epididymis glandular cells High Enhanced O00559 +ENSG00000147654 EBAG9 prostate glandular cells High Enhanced O00559 +ENSG00000147654 EBAG9 seminal vesicle glandular cells High Enhanced O00559 +ENSG00000147654 EBAG9 testis cells in seminiferous ducts Medium Enhanced O00559 +ENSG00000147654 EBAG9 testis Leydig cells Medium Enhanced O00559 +ENSG00000147813 NAPRT epididymis glandular cells Low Enhanced C9J8U2 +ENSG00000147813 NAPRT prostate glandular cells Low Enhanced C9J8U2 +ENSG00000147813 NAPRT seminal vesicle glandular cells Low Enhanced C9J8U2 +ENSG00000147813 NAPRT testis cells in seminiferous ducts Low Enhanced C9J8U2 +ENSG00000147813 NAPRT testis Leydig cells Low Enhanced C9J8U2 +ENSG00000147853 AK3 epididymis glandular cells Medium Enhanced Q9UIJ7 +ENSG00000147853 AK3 prostate glandular cells Medium Enhanced Q9UIJ7 +ENSG00000147853 AK3 seminal vesicle glandular cells Medium Enhanced Q9UIJ7 +ENSG00000147853 AK3 testis cells in seminiferous ducts Medium Enhanced Q9UIJ7 +ENSG00000147853 AK3 testis Leydig cells Medium Enhanced Q9UIJ7 +ENSG00000147862 NFIB epididymis glandular cells Medium Supported O00712 +ENSG00000147862 NFIB prostate glandular cells High Supported O00712 +ENSG00000147862 NFIB seminal vesicle glandular cells High Supported O00712 +ENSG00000147862 NFIB testis cells in seminiferous ducts Low Supported O00712 +ENSG00000147862 NFIB testis Leydig cells Low Supported O00712 +ENSG00000147872 PLIN2 epididymis glandular cells Low Supported Q99541 +ENSG00000147872 PLIN2 testis cells in seminiferous ducts Medium Supported Q99541 +ENSG00000147872 PLIN2 testis Leydig cells Low Supported Q99541 +ENSG00000148053 NTRK2 testis Leydig cells Low Enhanced Q16620 +ENSG00000148057 IDNK prostate glandular cells Medium Enhanced Q5T6J7 +ENSG00000148057 IDNK seminal vesicle glandular cells Medium Enhanced Q5T6J7 +ENSG00000148057 IDNK testis cells in seminiferous ducts High Enhanced Q5T6J7 +ENSG00000148057 IDNK testis Leydig cells Medium Enhanced Q5T6J7 +ENSG00000148090 AUH epididymis glandular cells Medium Enhanced Q13825 +ENSG00000148090 AUH prostate glandular cells Medium Enhanced Q13825 +ENSG00000148090 AUH seminal vesicle glandular cells High Enhanced Q13825 +ENSG00000148090 AUH testis cells in seminiferous ducts Low Enhanced Q13825 +ENSG00000148090 AUH testis Leydig cells Medium Enhanced Q13825 +ENSG00000148156 ACTL7B testis elongated or late spermatids High Enhanced Q9Y614 +ENSG00000148156 ACTL7B testis Leydig cells Low Enhanced Q9Y614 +ENSG00000148156 ACTL7B testis pachytene spermatocytes Medium Enhanced Q9Y614 +ENSG00000148156 ACTL7B testis preleptotene spermatocytes Medium Enhanced Q9Y614 +ENSG00000148156 ACTL7B testis round or early spermatids Medium Enhanced Q9Y614 +ENSG00000148156 ACTL7B testis spermatogonia Low Enhanced Q9Y614 +ENSG00000148187 MRRF epididymis glandular cells Medium Enhanced Q96E11 +ENSG00000148187 MRRF prostate glandular cells Medium Enhanced Q96E11 +ENSG00000148187 MRRF seminal vesicle glandular cells Medium Enhanced Q96E11 +ENSG00000148187 MRRF testis cells in seminiferous ducts Medium Enhanced Q96E11 +ENSG00000148187 MRRF testis Leydig cells Medium Enhanced Q96E11 +ENSG00000148218 ALAD epididymis glandular cells Low Enhanced P13716 +ENSG00000148218 ALAD prostate glandular cells Medium Enhanced P13716 +ENSG00000148218 ALAD testis cells in seminiferous ducts Medium Enhanced P13716 +ENSG00000148218 ALAD testis Leydig cells Medium Enhanced P13716 +ENSG00000148308 GTF3C5 epididymis glandular cells High Supported Q9Y5Q8 +ENSG00000148308 GTF3C5 prostate glandular cells High Supported Q9Y5Q8 +ENSG00000148308 GTF3C5 seminal vesicle glandular cells Medium Supported Q9Y5Q8 +ENSG00000148308 GTF3C5 testis cells in seminiferous ducts Medium Supported Q9Y5Q8 +ENSG00000148308 GTF3C5 testis Leydig cells Medium Supported Q9Y5Q8 +ENSG00000148344 PTGES seminal vesicle glandular cells High Enhanced O14684 +ENSG00000148344 PTGES testis cells in seminiferous ducts Medium Enhanced O14684 +ENSG00000148344 PTGES testis Leydig cells Medium Enhanced O14684 +ENSG00000148356 LRSAM1 epididymis glandular cells Medium Supported Q6UWE0 +ENSG00000148356 LRSAM1 prostate glandular cells Medium Supported Q6UWE0 +ENSG00000148356 LRSAM1 seminal vesicle glandular cells Medium Supported Q6UWE0 +ENSG00000148356 LRSAM1 testis cells in seminiferous ducts Low Supported Q6UWE0 +ENSG00000148356 LRSAM1 testis Leydig cells Low Supported Q6UWE0 +ENSG00000148357 HMCN2 prostate glandular cells Low Enhanced Q8NDA2 +ENSG00000148357 HMCN2 seminal vesicle glandular cells Low Enhanced Q8NDA2 +ENSG00000148357 HMCN2 testis cells in seminiferous ducts Low Enhanced Q8NDA2 +ENSG00000148357 HMCN2 testis Leydig cells High Enhanced Q8NDA2 +ENSG00000148358 GPR107 epididymis glandular cells High Supported Q5VW38 +ENSG00000148358 GPR107 prostate glandular cells High Supported Q5VW38 +ENSG00000148358 GPR107 seminal vesicle glandular cells Medium Supported Q5VW38 +ENSG00000148358 GPR107 testis cells in seminiferous ducts Medium Supported Q5VW38 +ENSG00000148358 GPR107 testis Leydig cells Medium Supported Q5VW38 +ENSG00000148386 LCN9 epididymis glandular cells High Enhanced Q8WX39 +ENSG00000148396 SEC16A epididymis glandular cells Medium Supported O15027 +ENSG00000148396 SEC16A prostate glandular cells Medium Supported O15027 +ENSG00000148396 SEC16A seminal vesicle glandular cells Medium Supported O15027 +ENSG00000148396 SEC16A testis cells in seminiferous ducts Medium Supported O15027 +ENSG00000148396 SEC16A testis Leydig cells Low Supported O15027 +ENSG00000148400 NOTCH1 epididymis glandular cells Medium Supported P46531 +ENSG00000148400 NOTCH1 prostate glandular cells Medium Supported P46531 +ENSG00000148400 NOTCH1 seminal vesicle glandular cells Medium Supported P46531 +ENSG00000148400 NOTCH1 testis cells in seminiferous ducts High Supported P46531 +ENSG00000148400 NOTCH1 testis Leydig cells Medium Supported P46531 +ENSG00000148450 MSRB2 epididymis glandular cells Low Enhanced Q9Y3D2 +ENSG00000148450 MSRB2 prostate glandular cells Medium Enhanced Q9Y3D2 +ENSG00000148450 MSRB2 seminal vesicle glandular cells Medium Enhanced Q9Y3D2 +ENSG00000148450 MSRB2 testis cells in seminiferous ducts Low Enhanced Q9Y3D2 +ENSG00000148450 MSRB2 testis Leydig cells Medium Enhanced Q9Y3D2 +ENSG00000148516 ZEB1 testis cells in seminiferous ducts Low Enhanced P37275 +ENSG00000148688 RPP30 epididymis glandular cells Low Enhanced P78346 +ENSG00000148688 RPP30 prostate glandular cells Low Enhanced P78346 +ENSG00000148688 RPP30 seminal vesicle glandular cells Low Enhanced P78346 +ENSG00000148688 RPP30 testis cells in seminiferous ducts Low Enhanced P78346 +ENSG00000148688 RPP30 testis Leydig cells Medium Enhanced P78346 +ENSG00000148700 ADD3 epididymis glandular cells High Supported Q9UEY8 +ENSG00000148700 ADD3 prostate glandular cells High Supported Q9UEY8 +ENSG00000148700 ADD3 seminal vesicle glandular cells High Supported Q9UEY8 +ENSG00000148700 ADD3 testis cells in seminiferous ducts High Supported Q9UEY8 +ENSG00000148700 ADD3 testis Leydig cells Medium Supported Q9UEY8 +ENSG00000148737 TCF7L2 epididymis glandular cells High Supported Q9NQB0 +ENSG00000148737 TCF7L2 prostate glandular cells High Supported Q9NQB0 +ENSG00000148737 TCF7L2 seminal vesicle glandular cells High Supported Q9NQB0 +ENSG00000148737 TCF7L2 testis cells in seminiferous ducts High Supported Q9NQB0 +ENSG00000148737 TCF7L2 testis Leydig cells High Supported Q9NQB0 +ENSG00000148773 MKI67 epididymis glandular cells Low Enhanced P46013 +ENSG00000148773 MKI67 testis cells in seminiferous ducts Low Enhanced P46013 +ENSG00000148795 CYP17A1 testis Leydig cells High Enhanced P05093 +ENSG00000148814 LRRC27 testis cells in seminiferous ducts Low Enhanced Q9C0I9 +ENSG00000148814 LRRC27 testis Leydig cells Low Enhanced Q9C0I9 +ENSG00000148834 GSTO1 seminal vesicle glandular cells Low Enhanced P78417 +ENSG00000148834 GSTO1 testis Leydig cells Low Enhanced P78417 +ENSG00000148835 TAF5 epididymis glandular cells High Supported Q15542 +ENSG00000148835 TAF5 prostate glandular cells High Supported Q15542 +ENSG00000148835 TAF5 seminal vesicle glandular cells Medium Supported Q15542 +ENSG00000148835 TAF5 testis cells in seminiferous ducts High Supported Q15542 +ENSG00000148835 TAF5 testis Leydig cells High Supported Q15542 +ENSG00000148908 RGS10 testis Leydig cells Low Enhanced O43665 +ENSG00000148935 GAS2 testis cells in seminiferous ducts Low Enhanced O43903 +ENSG00000148942 SLC5A12 epididymis glandular cells Low Enhanced Q1EHB4 +ENSG00000148965 SAA4 testis cells in seminiferous ducts Medium Supported P35542 +ENSG00000148965 SAA4 testis Leydig cells Medium Supported P35542 +ENSG00000149054 ZNF215 epididymis glandular cells Low Enhanced Q9UL58 +ENSG00000149054 ZNF215 seminal vesicle glandular cells Low Enhanced Q9UL58 +ENSG00000149054 ZNF215 testis cells in seminiferous ducts Low Enhanced Q9UL58 +ENSG00000149115 TNKS1BP1 epididymis glandular cells High Enhanced Q9C0C2 +ENSG00000149115 TNKS1BP1 prostate glandular cells High Enhanced Q9C0C2 +ENSG00000149115 TNKS1BP1 seminal vesicle glandular cells High Enhanced Q9C0C2 +ENSG00000149115 TNKS1BP1 testis cells in seminiferous ducts Low Enhanced Q9C0C2 +ENSG00000149115 TNKS1BP1 testis Leydig cells Medium Enhanced Q9C0C2 +ENSG00000149150 SLC43A1 epididymis glandular cells Medium Enhanced O75387 +ENSG00000149150 SLC43A1 prostate glandular cells Medium Enhanced O75387 +ENSG00000149150 SLC43A1 seminal vesicle glandular cells High Enhanced O75387 +ENSG00000149150 SLC43A1 testis cells in seminiferous ducts Medium Enhanced O75387 +ENSG00000149150 SLC43A1 testis Leydig cells Medium Enhanced O75387 +ENSG00000149182 ARFGAP2 epididymis glandular cells Medium Enhanced Q8N6H7 +ENSG00000149182 ARFGAP2 prostate glandular cells Low Enhanced Q8N6H7 +ENSG00000149182 ARFGAP2 seminal vesicle glandular cells Medium Enhanced Q8N6H7 +ENSG00000149182 ARFGAP2 testis cells in seminiferous ducts Medium Enhanced Q8N6H7 +ENSG00000149182 ARFGAP2 testis Leydig cells Medium Enhanced Q8N6H7 +ENSG00000149187 CELF1 epididymis glandular cells High Supported Q92879 +ENSG00000149187 CELF1 prostate glandular cells Medium Supported Q92879 +ENSG00000149187 CELF1 seminal vesicle glandular cells Medium Supported Q92879 +ENSG00000149187 CELF1 testis cells in seminiferous ducts High Supported Q92879 +ENSG00000149187 CELF1 testis Leydig cells Medium Supported Q92879 +ENSG00000149218 ENDOD1 epididymis glandular cells Low Enhanced O94919 +ENSG00000149218 ENDOD1 prostate glandular cells High Enhanced O94919 +ENSG00000149218 ENDOD1 seminal vesicle glandular cells Low Enhanced O94919 +ENSG00000149218 ENDOD1 testis cells in seminiferous ducts Medium Enhanced O94919 +ENSG00000149218 ENDOD1 testis Leydig cells Medium Enhanced O94919 +ENSG00000149257 SERPINH1 testis cells in seminiferous ducts Medium Supported P50454 +ENSG00000149257 SERPINH1 testis Leydig cells Medium Supported P50454 +ENSG00000149269 PAK1 epididymis glandular cells Medium Enhanced Q13153 +ENSG00000149269 PAK1 prostate glandular cells Medium Enhanced Q13153 +ENSG00000149269 PAK1 seminal vesicle glandular cells Medium Enhanced Q13153 +ENSG00000149269 PAK1 testis cells in seminiferous ducts Medium Enhanced Q13153 +ENSG00000149269 PAK1 testis Leydig cells Medium Enhanced Q13153 +ENSG00000149311 ATM epididymis glandular cells High Supported Q13315 +ENSG00000149311 ATM prostate glandular cells High Supported Q13315 +ENSG00000149311 ATM seminal vesicle glandular cells High Supported Q13315 +ENSG00000149311 ATM testis cells in seminiferous ducts High Supported Q13315 +ENSG00000149311 ATM testis Leydig cells Medium Supported Q13315 +ENSG00000149476 TKFC epididymis glandular cells Low Enhanced Q3LXA3 +ENSG00000149476 TKFC prostate glandular cells Low Enhanced Q3LXA3 +ENSG00000149476 TKFC seminal vesicle glandular cells Low Enhanced Q3LXA3 +ENSG00000149476 TKFC testis cells in seminiferous ducts Low Enhanced Q3LXA3 +ENSG00000149476 TKFC testis Leydig cells Medium Enhanced Q3LXA3 +ENSG00000149480 MTA2 epididymis glandular cells High Enhanced O94776 +ENSG00000149480 MTA2 prostate glandular cells High Enhanced O94776 +ENSG00000149480 MTA2 seminal vesicle glandular cells High Enhanced O94776 +ENSG00000149480 MTA2 testis cells in seminiferous ducts High Enhanced O94776 +ENSG00000149480 MTA2 testis Leydig cells High Enhanced O94776 +ENSG00000149503 INCENP testis cells in seminiferous ducts High Enhanced Q9NQS7 +ENSG00000149503 INCENP testis Leydig cells Low Enhanced Q9NQS7 +ENSG00000149507 OOSP2 epididymis glandular cells Low Enhanced Q86WS3 +ENSG00000149507 OOSP2 testis preleptotene spermatocytes Medium Enhanced Q86WS3 +ENSG00000149507 OOSP2 testis spermatogonia High Enhanced Q86WS3 +ENSG00000149532 CPSF7 epididymis glandular cells High Supported Q8N684 +ENSG00000149532 CPSF7 prostate glandular cells Low Supported Q8N684 +ENSG00000149532 CPSF7 seminal vesicle glandular cells Medium Supported Q8N684 +ENSG00000149532 CPSF7 testis cells in seminiferous ducts High Supported Q8N684 +ENSG00000149532 CPSF7 testis Leydig cells Medium Supported Q8N684 +ENSG00000149599 DUSP15 testis cells in seminiferous ducts Low Enhanced Q9H1R2 +ENSG00000149599 DUSP15 testis Leydig cells Medium Enhanced Q9H1R2 +ENSG00000149609 C20orf144 testis elongated or late spermatids Medium Enhanced Q9BQM9 +ENSG00000149609 C20orf144 testis round or early spermatids High Enhanced Q9BQM9 +ENSG00000149636 DSN1 epididymis glandular cells High Enhanced Q9H410 +ENSG00000149636 DSN1 prostate glandular cells Medium Enhanced Q9H410 +ENSG00000149636 DSN1 seminal vesicle glandular cells Medium Enhanced Q9H410 +ENSG00000149636 DSN1 testis cells in seminiferous ducts Medium Enhanced Q9H410 +ENSG00000149636 DSN1 testis Leydig cells Medium Enhanced Q9H410 +ENSG00000149651 SPINT4 epididymis glandular cells High Enhanced Q6UDR6 +ENSG00000149806 FAU epididymis glandular cells Medium Supported P62861 +ENSG00000149806 FAU prostate glandular cells Medium Supported P62861 +ENSG00000149806 FAU seminal vesicle glandular cells Medium Supported P62861 +ENSG00000149806 FAU testis Leydig cells Medium Supported P62861 +ENSG00000149923 PPP4C epididymis glandular cells Medium Enhanced P60510 +ENSG00000149923 PPP4C prostate glandular cells High Enhanced P60510 +ENSG00000149923 PPP4C seminal vesicle glandular cells Medium Enhanced P60510 +ENSG00000149923 PPP4C testis cells in seminiferous ducts High Enhanced P60510 +ENSG00000149923 PPP4C testis Leydig cells Medium Enhanced P60510 +ENSG00000149925 ALDOA epididymis glandular cells Medium Enhanced P04075 +ENSG00000149925 ALDOA prostate glandular cells Medium Enhanced P04075 +ENSG00000149925 ALDOA seminal vesicle glandular cells Medium Enhanced P04075 +ENSG00000149925 ALDOA testis cells in seminiferous ducts Low Enhanced P04075 +ENSG00000149925 ALDOA testis Leydig cells Medium Enhanced P04075 +ENSG00000150054 MPP7 epididymis glandular cells High Enhanced Q5T2T1 +ENSG00000150054 MPP7 prostate glandular cells Medium Enhanced Q5T2T1 +ENSG00000150054 MPP7 seminal vesicle glandular cells High Enhanced Q5T2T1 +ENSG00000150054 MPP7 testis cells in seminiferous ducts High Enhanced Q5T2T1 +ENSG00000150054 MPP7 testis Leydig cells Medium Enhanced Q5T2T1 +ENSG00000150093 ITGB1 seminal vesicle glandular cells Low Enhanced P05556 +ENSG00000150316 CWC15 epididymis glandular cells Medium Supported Q9P013 +ENSG00000150316 CWC15 prostate glandular cells Low Supported Q9P013 +ENSG00000150316 CWC15 seminal vesicle glandular cells Low Supported Q9P013 +ENSG00000150316 CWC15 testis cells in seminiferous ducts High Supported Q9P013 +ENSG00000150316 CWC15 testis Leydig cells Medium Supported Q9P013 +ENSG00000150459 SAP18 epididymis glandular cells High Supported O00422 +ENSG00000150459 SAP18 prostate glandular cells Medium Supported O00422 +ENSG00000150459 SAP18 seminal vesicle glandular cells Medium Supported O00422 +ENSG00000150459 SAP18 testis cells in seminiferous ducts High Supported O00422 +ENSG00000150459 SAP18 testis Leydig cells Medium Supported O00422 +ENSG00000150526 MIA2 epididymis glandular cells Medium Supported NA +ENSG00000150526 MIA2 prostate glandular cells Low Supported NA +ENSG00000150526 MIA2 testis cells in seminiferous ducts Low Supported NA +ENSG00000150593 PDCD4 epididymis glandular cells High Supported Q53EL6 +ENSG00000150593 PDCD4 prostate glandular cells High Supported Q53EL6 +ENSG00000150593 PDCD4 seminal vesicle glandular cells High Supported Q53EL6 +ENSG00000150593 PDCD4 testis cells in seminiferous ducts High Supported Q53EL6 +ENSG00000150593 PDCD4 testis Leydig cells High Supported Q53EL6 +ENSG00000150628 SPATA4 testis pachytene spermatocytes Medium Enhanced Q8NEY3 +ENSG00000150628 SPATA4 testis round or early spermatids Medium Enhanced Q8NEY3 +ENSG00000150712 MTMR12 epididymis glandular cells Medium Supported Q9C0I1 +ENSG00000150712 MTMR12 prostate glandular cells High Supported Q9C0I1 +ENSG00000150712 MTMR12 seminal vesicle glandular cells High Supported Q9C0I1 +ENSG00000150712 MTMR12 testis cells in seminiferous ducts High Supported Q9C0I1 +ENSG00000150712 MTMR12 testis Leydig cells High Supported Q9C0I1 +ENSG00000150753 CCT5 epididymis glandular cells Medium Enhanced P48643 +ENSG00000150753 CCT5 prostate glandular cells Low Enhanced P48643 +ENSG00000150753 CCT5 seminal vesicle glandular cells Low Enhanced P48643 +ENSG00000150753 CCT5 testis cells in seminiferous ducts High Enhanced P48643 +ENSG00000150753 CCT5 testis Leydig cells Medium Enhanced P48643 +ENSG00000150768 DLAT epididymis glandular cells Medium Enhanced P10515 +ENSG00000150768 DLAT prostate glandular cells Medium Enhanced P10515 +ENSG00000150768 DLAT testis cells in seminiferous ducts Medium Enhanced P10515 +ENSG00000150768 DLAT testis Leydig cells Low Enhanced P10515 +ENSG00000150782 IL18 epididymis glandular cells Medium Enhanced Q14116 +ENSG00000150782 IL18 prostate glandular cells Low Enhanced Q14116 +ENSG00000150782 IL18 seminal vesicle glandular cells Medium Enhanced Q14116 +ENSG00000150782 IL18 testis cells in seminiferous ducts Low Enhanced Q14116 +ENSG00000150783 TEX12 testis elongated or late spermatids Medium Enhanced Q9BXU0 +ENSG00000150783 TEX12 testis pachytene spermatocytes High Enhanced Q9BXU0 +ENSG00000150783 TEX12 testis round or early spermatids High Enhanced Q9BXU0 +ENSG00000150867 PIP4K2A epididymis glandular cells Medium Supported P48426 +ENSG00000150867 PIP4K2A prostate glandular cells High Supported P48426 +ENSG00000150867 PIP4K2A seminal vesicle glandular cells High Supported P48426 +ENSG00000150867 PIP4K2A testis cells in seminiferous ducts Medium Supported P48426 +ENSG00000150867 PIP4K2A testis Leydig cells High Supported P48426 +ENSG00000150938 CRIM1 epididymis glandular cells Medium Enhanced Q9NZV1 +ENSG00000150938 CRIM1 prostate glandular cells Low Enhanced Q9NZV1 +ENSG00000150938 CRIM1 seminal vesicle glandular cells Low Enhanced Q9NZV1 +ENSG00000150938 CRIM1 testis cells in seminiferous ducts Medium Enhanced Q9NZV1 +ENSG00000150938 CRIM1 testis Leydig cells Medium Enhanced Q9NZV1 +ENSG00000150990 DHX37 epididymis glandular cells Medium Enhanced Q8IY37 +ENSG00000150990 DHX37 prostate glandular cells Low Enhanced Q8IY37 +ENSG00000150990 DHX37 seminal vesicle glandular cells Medium Enhanced Q8IY37 +ENSG00000150990 DHX37 testis cells in seminiferous ducts Low Enhanced Q8IY37 +ENSG00000150991 UBC epididymis glandular cells Medium Supported P0CG48 +ENSG00000150991 UBC prostate glandular cells High Supported P0CG48 +ENSG00000150991 UBC seminal vesicle glandular cells Medium Supported P0CG48 +ENSG00000150991 UBC testis cells in seminiferous ducts High Supported P0CG48 +ENSG00000150991 UBC testis Leydig cells Medium Supported P0CG48 +ENSG00000151067 CACNA1C epididymis glandular cells Medium Enhanced Q13936 +ENSG00000151067 CACNA1C prostate glandular cells Low Enhanced Q13936 +ENSG00000151067 CACNA1C seminal vesicle glandular cells Medium Enhanced Q13936 +ENSG00000151067 CACNA1C testis Leydig cells High Enhanced Q13936 +ENSG00000151093 OXSM epididymis glandular cells Medium Enhanced Q9NWU1 +ENSG00000151093 OXSM prostate glandular cells High Enhanced Q9NWU1 +ENSG00000151093 OXSM seminal vesicle glandular cells High Enhanced Q9NWU1 +ENSG00000151093 OXSM testis cells in seminiferous ducts High Enhanced Q9NWU1 +ENSG00000151093 OXSM testis Leydig cells High Enhanced Q9NWU1 +ENSG00000151240 DIP2C epididymis glandular cells Medium Enhanced Q9Y2E4 +ENSG00000151240 DIP2C prostate glandular cells Medium Enhanced Q9Y2E4 +ENSG00000151240 DIP2C seminal vesicle glandular cells High Enhanced Q9Y2E4 +ENSG00000151240 DIP2C testis cells in seminiferous ducts Medium Enhanced Q9Y2E4 +ENSG00000151240 DIP2C testis Leydig cells Medium Enhanced Q9Y2E4 +ENSG00000151247 EIF4E epididymis glandular cells Medium Supported P06730 +ENSG00000151247 EIF4E prostate glandular cells Medium Supported P06730 +ENSG00000151247 EIF4E seminal vesicle glandular cells Medium Supported P06730 +ENSG00000151247 EIF4E testis cells in seminiferous ducts Medium Supported P06730 +ENSG00000151247 EIF4E testis Leydig cells Medium Supported P06730 +ENSG00000151276 MAGI1 seminal vesicle glandular cells Medium Enhanced NA +ENSG00000151287 TEX30 epididymis glandular cells Low Enhanced Q5JUR7 +ENSG00000151287 TEX30 testis elongated or late spermatids High Enhanced Q5JUR7 +ENSG00000151287 TEX30 testis Leydig cells Low Enhanced Q5JUR7 +ENSG00000151287 TEX30 testis pachytene spermatocytes High Enhanced Q5JUR7 +ENSG00000151287 TEX30 testis preleptotene spermatocytes Medium Enhanced Q5JUR7 +ENSG00000151287 TEX30 testis round or early spermatids High Enhanced Q5JUR7 +ENSG00000151287 TEX30 testis spermatogonia Low Enhanced Q5JUR7 +ENSG00000151322 NPAS3 testis cells in seminiferous ducts Low Enhanced Q8IXF0 +ENSG00000151322 NPAS3 testis Leydig cells Low Enhanced Q8IXF0 +ENSG00000151332 MBIP epididymis glandular cells Low Supported Q9NS73 +ENSG00000151332 MBIP prostate glandular cells Medium Supported Q9NS73 +ENSG00000151332 MBIP seminal vesicle glandular cells Low Supported Q9NS73 +ENSG00000151332 MBIP testis cells in seminiferous ducts Medium Supported Q9NS73 +ENSG00000151332 MBIP testis Leydig cells Low Supported Q9NS73 +ENSG00000151338 MIPOL1 epididymis glandular cells Low Enhanced Q8TD10 +ENSG00000151338 MIPOL1 prostate glandular cells High Enhanced Q8TD10 +ENSG00000151338 MIPOL1 seminal vesicle glandular cells Medium Enhanced Q8TD10 +ENSG00000151338 MIPOL1 testis cells in seminiferous ducts Low Enhanced Q8TD10 +ENSG00000151338 MIPOL1 testis Leydig cells Medium Enhanced Q8TD10 +ENSG00000151364 KCTD14 seminal vesicle glandular cells High Enhanced Q9BQ13 +ENSG00000151498 ACAD8 epididymis glandular cells Medium Enhanced Q9UKU7 +ENSG00000151498 ACAD8 prostate glandular cells High Enhanced Q9UKU7 +ENSG00000151498 ACAD8 seminal vesicle glandular cells Medium Enhanced Q9UKU7 +ENSG00000151498 ACAD8 testis cells in seminiferous ducts High Enhanced Q9UKU7 +ENSG00000151498 ACAD8 testis Leydig cells High Enhanced Q9UKU7 +ENSG00000151500 THYN1 epididymis glandular cells Medium Supported Q9P016 +ENSG00000151500 THYN1 prostate glandular cells Medium Supported Q9P016 +ENSG00000151500 THYN1 seminal vesicle glandular cells High Supported Q9P016 +ENSG00000151500 THYN1 testis cells in seminiferous ducts Medium Supported Q9P016 +ENSG00000151500 THYN1 testis Leydig cells High Supported Q9P016 +ENSG00000151532 VTI1A epididymis glandular cells High Supported Q96AJ9 +ENSG00000151532 VTI1A prostate glandular cells Medium Supported Q96AJ9 +ENSG00000151532 VTI1A seminal vesicle glandular cells Medium Supported Q96AJ9 +ENSG00000151532 VTI1A testis cells in seminiferous ducts Low Supported Q96AJ9 +ENSG00000151532 VTI1A testis Leydig cells Low Supported Q96AJ9 +ENSG00000151552 QDPR epididymis glandular cells Low Enhanced P09417 +ENSG00000151623 NR3C2 epididymis glandular cells Medium Enhanced P08235 +ENSG00000151623 NR3C2 prostate glandular cells High Enhanced P08235 +ENSG00000151623 NR3C2 seminal vesicle glandular cells Medium Enhanced P08235 +ENSG00000151623 NR3C2 testis cells in seminiferous ducts Medium Enhanced P08235 +ENSG00000151623 NR3C2 testis Leydig cells High Enhanced P08235 +ENSG00000151632 AKR1C2 testis Leydig cells Medium Enhanced P52895 +ENSG00000151689 INPP1 epididymis glandular cells Low Supported P49441 +ENSG00000151689 INPP1 prostate glandular cells Low Supported P49441 +ENSG00000151689 INPP1 seminal vesicle glandular cells Low Supported P49441 +ENSG00000151689 INPP1 testis Leydig cells Medium Supported P49441 +ENSG00000151726 ACSL1 prostate glandular cells Medium Enhanced P33121 +ENSG00000151726 ACSL1 testis cells in seminiferous ducts Low Enhanced P33121 +ENSG00000151726 ACSL1 testis Leydig cells Medium Enhanced P33121 +ENSG00000151882 CCL28 testis Leydig cells Low Supported Q9NRJ3 +ENSG00000151917 BEND6 epididymis glandular cells Low Enhanced Q5SZJ8 +ENSG00000151917 BEND6 seminal vesicle glandular cells Low Enhanced Q5SZJ8 +ENSG00000151917 BEND6 testis cells in seminiferous ducts Medium Enhanced Q5SZJ8 +ENSG00000151929 BAG3 epididymis glandular cells Medium Enhanced O95817 +ENSG00000151929 BAG3 prostate glandular cells Medium Enhanced O95817 +ENSG00000151929 BAG3 seminal vesicle glandular cells Medium Enhanced O95817 +ENSG00000151929 BAG3 testis cells in seminiferous ducts Medium Enhanced O95817 +ENSG00000151929 BAG3 testis Leydig cells Medium Enhanced O95817 +ENSG00000152102 FAM168B testis Leydig cells Low Enhanced A1KXE4 +ENSG00000152133 GPATCH11 epididymis glandular cells Medium Enhanced Q8N954 +ENSG00000152133 GPATCH11 prostate glandular cells High Enhanced Q8N954 +ENSG00000152133 GPATCH11 seminal vesicle glandular cells Medium Enhanced Q8N954 +ENSG00000152133 GPATCH11 testis cells in seminiferous ducts High Enhanced Q8N954 +ENSG00000152133 GPATCH11 testis Leydig cells High Enhanced Q8N954 +ENSG00000152192 POU4F1 testis elongated or late spermatids High Enhanced Q01851 +ENSG00000152193 RNF219 epididymis glandular cells Medium Enhanced Q5W0B1 +ENSG00000152193 RNF219 prostate glandular cells Low Enhanced Q5W0B1 +ENSG00000152193 RNF219 seminal vesicle glandular cells Medium Enhanced Q5W0B1 +ENSG00000152193 RNF219 testis cells in seminiferous ducts Medium Enhanced Q5W0B1 +ENSG00000152193 RNF219 testis Leydig cells Low Enhanced Q5W0B1 +ENSG00000152208 GRID2 testis cells in seminiferous ducts Medium Enhanced O43424 +ENSG00000152208 GRID2 testis Leydig cells Low Enhanced O43424 +ENSG00000152229 PSTPIP2 prostate glandular cells Medium Enhanced Q9H939 +ENSG00000152234 ATP5A1 epididymis glandular cells High Enhanced P25705 +ENSG00000152234 ATP5A1 prostate glandular cells High Enhanced P25705 +ENSG00000152234 ATP5A1 seminal vesicle glandular cells High Enhanced P25705 +ENSG00000152234 ATP5A1 testis cells in seminiferous ducts High Enhanced P25705 +ENSG00000152234 ATP5A1 testis Leydig cells High Enhanced P25705 +ENSG00000152240 HAUS1 epididymis glandular cells Medium Supported Q96CS2 +ENSG00000152240 HAUS1 prostate glandular cells Medium Supported Q96CS2 +ENSG00000152240 HAUS1 seminal vesicle glandular cells Medium Supported Q96CS2 +ENSG00000152240 HAUS1 testis cells in seminiferous ducts High Supported Q96CS2 +ENSG00000152240 HAUS1 testis Leydig cells Medium Supported Q96CS2 +ENSG00000152291 TGOLN2 epididymis glandular cells High Enhanced O43493 +ENSG00000152291 TGOLN2 prostate glandular cells High Enhanced O43493 +ENSG00000152291 TGOLN2 seminal vesicle glandular cells High Enhanced O43493 +ENSG00000152291 TGOLN2 testis cells in seminiferous ducts Medium Enhanced O43493 +ENSG00000152291 TGOLN2 testis Leydig cells Medium Enhanced O43493 +ENSG00000152422 XRCC4 epididymis glandular cells High Enhanced Q13426 +ENSG00000152422 XRCC4 prostate glandular cells Medium Enhanced Q13426 +ENSG00000152422 XRCC4 seminal vesicle glandular cells Medium Enhanced Q13426 +ENSG00000152422 XRCC4 testis cells in seminiferous ducts High Enhanced Q13426 +ENSG00000152422 XRCC4 testis Leydig cells High Enhanced Q13426 +ENSG00000152430 BOLL testis elongated or late spermatids Medium Enhanced Q8N9W6 +ENSG00000152430 BOLL testis Leydig cells Low Enhanced Q8N9W6 +ENSG00000152430 BOLL testis pachytene spermatocytes High Enhanced Q8N9W6 +ENSG00000152430 BOLL testis preleptotene spermatocytes Low Enhanced Q8N9W6 +ENSG00000152430 BOLL testis round or early spermatids High Enhanced Q8N9W6 +ENSG00000152430 BOLL testis spermatogonia Low Enhanced Q8N9W6 +ENSG00000152455 SUV39H2 testis elongated or late spermatids High Enhanced Q9H5I1 +ENSG00000152455 SUV39H2 testis Leydig cells Low Enhanced Q9H5I1 +ENSG00000152455 SUV39H2 testis pachytene spermatocytes Medium Enhanced Q9H5I1 +ENSG00000152455 SUV39H2 testis round or early spermatids High Enhanced Q9H5I1 +ENSG00000152463 OLAH epididymis glandular cells Low Enhanced Q9NV23 +ENSG00000152463 OLAH testis cells in seminiferous ducts Medium Enhanced Q9NV23 +ENSG00000152583 SPARCL1 epididymis glandular cells Low Enhanced Q14515 +ENSG00000152583 SPARCL1 testis Leydig cells High Enhanced Q14515 +ENSG00000152601 MBNL1 epididymis glandular cells Medium Enhanced Q9NR56 +ENSG00000152601 MBNL1 prostate glandular cells Medium Enhanced Q9NR56 +ENSG00000152601 MBNL1 seminal vesicle glandular cells Medium Enhanced Q9NR56 +ENSG00000152601 MBNL1 testis cells in seminiferous ducts Medium Enhanced Q9NR56 +ENSG00000152601 MBNL1 testis Leydig cells Medium Enhanced Q9NR56 +ENSG00000152611 CAPSL testis cells in seminiferous ducts Low Enhanced Q8WWF8 +ENSG00000152620 NADK2 epididymis glandular cells Medium Enhanced Q4G0N4 +ENSG00000152620 NADK2 prostate glandular cells Medium Enhanced Q4G0N4 +ENSG00000152620 NADK2 seminal vesicle glandular cells Medium Enhanced Q4G0N4 +ENSG00000152620 NADK2 testis cells in seminiferous ducts Medium Enhanced Q4G0N4 +ENSG00000152620 NADK2 testis Leydig cells High Enhanced Q4G0N4 +ENSG00000152661 GJA1 epididymis glandular cells Medium Enhanced P17302 +ENSG00000152661 GJA1 prostate glandular cells High Enhanced P17302 +ENSG00000152661 GJA1 seminal vesicle glandular cells Low Enhanced P17302 +ENSG00000152661 GJA1 testis cells in seminiferous ducts Medium Enhanced P17302 +ENSG00000152661 GJA1 testis Leydig cells High Enhanced P17302 +ENSG00000152670 DDX4 testis elongated or late spermatids High Enhanced Q9NQI0 +ENSG00000152670 DDX4 testis Leydig cells Low Enhanced Q9NQI0 +ENSG00000152670 DDX4 testis pachytene spermatocytes High Enhanced Q9NQI0 +ENSG00000152670 DDX4 testis preleptotene spermatocytes High Enhanced Q9NQI0 +ENSG00000152670 DDX4 testis round or early spermatids High Enhanced Q9NQI0 +ENSG00000152670 DDX4 testis spermatogonia High Enhanced Q9NQI0 +ENSG00000152700 SAR1B epididymis glandular cells Medium Supported Q9Y6B6 +ENSG00000152700 SAR1B prostate glandular cells Medium Supported Q9Y6B6 +ENSG00000152700 SAR1B testis cells in seminiferous ducts Medium Supported Q9Y6B6 +ENSG00000152700 SAR1B testis Leydig cells Medium Supported Q9Y6B6 +ENSG00000152795 HNRNPDL epididymis glandular cells High Supported O14979 +ENSG00000152795 HNRNPDL prostate glandular cells High Supported O14979 +ENSG00000152795 HNRNPDL seminal vesicle glandular cells High Supported O14979 +ENSG00000152795 HNRNPDL testis cells in seminiferous ducts High Supported O14979 +ENSG00000152795 HNRNPDL testis Leydig cells High Supported O14979 +ENSG00000152818 UTRN epididymis glandular cells Low Enhanced P46939 +ENSG00000152818 UTRN prostate glandular cells High Enhanced P46939 +ENSG00000152818 UTRN seminal vesicle glandular cells Medium Enhanced P46939 +ENSG00000152818 UTRN testis cells in seminiferous ducts Medium Enhanced P46939 +ENSG00000152818 UTRN testis Leydig cells Medium Enhanced P46939 +ENSG00000152904 GGPS1 prostate glandular cells Low Enhanced O95749 +ENSG00000152904 GGPS1 testis cells in seminiferous ducts Medium Enhanced O95749 +ENSG00000153046 CDYL epididymis glandular cells High Enhanced Q9Y232 +ENSG00000153046 CDYL prostate glandular cells Medium Enhanced Q9Y232 +ENSG00000153046 CDYL seminal vesicle glandular cells High Enhanced Q9Y232 +ENSG00000153046 CDYL testis cells in seminiferous ducts High Enhanced Q9Y232 +ENSG00000153046 CDYL testis Leydig cells High Enhanced Q9Y232 +ENSG00000153066 TXNDC11 epididymis glandular cells Medium Supported Q6PKC3 +ENSG00000153066 TXNDC11 prostate glandular cells Medium Supported Q6PKC3 +ENSG00000153066 TXNDC11 seminal vesicle glandular cells Medium Supported Q6PKC3 +ENSG00000153066 TXNDC11 testis cells in seminiferous ducts Medium Supported Q6PKC3 +ENSG00000153066 TXNDC11 testis Leydig cells Medium Supported Q6PKC3 +ENSG00000153071 DAB2 epididymis glandular cells Medium Enhanced P98082 +ENSG00000153071 DAB2 prostate glandular cells Low Enhanced P98082 +ENSG00000153071 DAB2 testis cells in seminiferous ducts Low Enhanced P98082 +ENSG00000153071 DAB2 testis Leydig cells Low Enhanced P98082 +ENSG00000153132 CLGN prostate glandular cells Low Enhanced O14967 +ENSG00000153132 CLGN testis elongated or late spermatids Low Enhanced O14967 +ENSG00000153132 CLGN testis pachytene spermatocytes High Enhanced O14967 +ENSG00000153132 CLGN testis round or early spermatids High Enhanced O14967 +ENSG00000153147 SMARCA5 epididymis glandular cells Medium Supported O60264 +ENSG00000153147 SMARCA5 prostate glandular cells Medium Supported O60264 +ENSG00000153147 SMARCA5 seminal vesicle glandular cells Medium Supported O60264 +ENSG00000153147 SMARCA5 testis cells in seminiferous ducts Medium Supported O60264 +ENSG00000153147 SMARCA5 testis Leydig cells Low Supported O60264 +ENSG00000153179 RASSF3 epididymis glandular cells Medium Supported Q86WH2 +ENSG00000153179 RASSF3 prostate glandular cells Medium Supported Q86WH2 +ENSG00000153179 RASSF3 seminal vesicle glandular cells High Supported Q86WH2 +ENSG00000153179 RASSF3 testis cells in seminiferous ducts Medium Supported Q86WH2 +ENSG00000153179 RASSF3 testis Leydig cells High Supported Q86WH2 +ENSG00000153187 HNRNPU epididymis glandular cells High Supported Q00839 +ENSG00000153187 HNRNPU prostate glandular cells High Supported Q00839 +ENSG00000153187 HNRNPU seminal vesicle glandular cells High Supported Q00839 +ENSG00000153187 HNRNPU testis cells in seminiferous ducts High Supported Q00839 +ENSG00000153187 HNRNPU testis Leydig cells High Supported Q00839 +ENSG00000153201 RANBP2 epididymis glandular cells High Supported P49792 +ENSG00000153201 RANBP2 prostate glandular cells High Supported P49792 +ENSG00000153201 RANBP2 seminal vesicle glandular cells High Supported P49792 +ENSG00000153201 RANBP2 testis cells in seminiferous ducts High Supported P49792 +ENSG00000153201 RANBP2 testis Leydig cells High Supported P49792 +ENSG00000153294 ADGRF4 testis cells in seminiferous ducts Low Enhanced Q8IZF3 +ENSG00000153395 LPCAT1 epididymis glandular cells Low Enhanced Q8NF37 +ENSG00000153395 LPCAT1 prostate glandular cells Low Enhanced Q8NF37 +ENSG00000153395 LPCAT1 seminal vesicle glandular cells Medium Enhanced Q8NF37 +ENSG00000153395 LPCAT1 testis cells in seminiferous ducts Medium Enhanced Q8NF37 +ENSG00000153395 LPCAT1 testis Leydig cells Medium Enhanced Q8NF37 +ENSG00000153446 C16orf89 epididymis glandular cells Medium Enhanced Q6UX73 +ENSG00000153498 SPACA7 testis cells in seminiferous ducts High Enhanced NA +ENSG00000153767 GTF2E1 epididymis glandular cells High Enhanced P29083 +ENSG00000153767 GTF2E1 prostate glandular cells Medium Enhanced P29083 +ENSG00000153767 GTF2E1 seminal vesicle glandular cells Medium Enhanced P29083 +ENSG00000153767 GTF2E1 testis cells in seminiferous ducts High Enhanced P29083 +ENSG00000153767 GTF2E1 testis Leydig cells High Enhanced P29083 +ENSG00000153779 TGIF2LX testis preleptotene spermatocytes Low Supported Q8IUE1 +ENSG00000153779 TGIF2LX testis round or early spermatids High Supported Q8IUE1 +ENSG00000153779 TGIF2LX testis spermatogonia Medium Supported Q8IUE1 +ENSG00000153820 SPHKAP testis Leydig cells Low Enhanced Q2M3C7 +ENSG00000153827 TRIP12 epididymis glandular cells Medium Enhanced Q14669 +ENSG00000153827 TRIP12 prostate glandular cells Low Enhanced Q14669 +ENSG00000153827 TRIP12 seminal vesicle glandular cells Low Enhanced Q14669 +ENSG00000153827 TRIP12 testis cells in seminiferous ducts High Enhanced Q14669 +ENSG00000153827 TRIP12 testis Leydig cells Low Enhanced Q14669 +ENSG00000153879 CEBPG epididymis glandular cells Low Enhanced P53567 +ENSG00000153879 CEBPG prostate glandular cells Low Enhanced P53567 +ENSG00000153879 CEBPG seminal vesicle glandular cells Low Enhanced P53567 +ENSG00000153879 CEBPG testis cells in seminiferous ducts Medium Enhanced P53567 +ENSG00000153879 CEBPG testis Leydig cells Low Enhanced P53567 +ENSG00000153904 DDAH1 epididymis glandular cells High Enhanced O94760 +ENSG00000153904 DDAH1 prostate glandular cells High Enhanced O94760 +ENSG00000153904 DDAH1 seminal vesicle glandular cells High Enhanced O94760 +ENSG00000153904 DDAH1 testis cells in seminiferous ducts High Enhanced O94760 +ENSG00000153904 DDAH1 testis Leydig cells High Enhanced O94760 +ENSG00000153914 SREK1 epididymis glandular cells High Enhanced Q8WXA9 +ENSG00000153914 SREK1 prostate glandular cells Medium Enhanced Q8WXA9 +ENSG00000153914 SREK1 seminal vesicle glandular cells Medium Enhanced Q8WXA9 +ENSG00000153914 SREK1 testis cells in seminiferous ducts Medium Enhanced Q8WXA9 +ENSG00000153914 SREK1 testis Leydig cells Medium Enhanced Q8WXA9 +ENSG00000153936 HS2ST1 epididymis glandular cells High Supported Q7LGA3 +ENSG00000153936 HS2ST1 prostate glandular cells Medium Supported Q7LGA3 +ENSG00000153936 HS2ST1 seminal vesicle glandular cells Medium Supported Q7LGA3 +ENSG00000153936 HS2ST1 testis cells in seminiferous ducts Medium Supported Q7LGA3 +ENSG00000153936 HS2ST1 testis Leydig cells High Supported Q7LGA3 +ENSG00000153956 CACNA2D1 epididymis glandular cells Low Enhanced P54289 +ENSG00000153956 CACNA2D1 seminal vesicle glandular cells Low Enhanced P54289 +ENSG00000154040 CABYR testis elongated or late spermatids High Enhanced O75952 +ENSG00000154040 CABYR testis Leydig cells Low Enhanced O75952 +ENSG00000154079 SDHAF4 epididymis glandular cells Medium Supported Q5VUM1 +ENSG00000154079 SDHAF4 prostate glandular cells Medium Supported Q5VUM1 +ENSG00000154079 SDHAF4 seminal vesicle glandular cells Medium Supported Q5VUM1 +ENSG00000154079 SDHAF4 testis cells in seminiferous ducts High Supported Q5VUM1 +ENSG00000154079 SDHAF4 testis Leydig cells High Supported Q5VUM1 +ENSG00000154099 DNAAF1 testis cells in seminiferous ducts High Enhanced Q8NEP3 +ENSG00000154174 TOMM70 epididymis glandular cells Medium Enhanced O94826 +ENSG00000154174 TOMM70 prostate glandular cells Low Enhanced O94826 +ENSG00000154174 TOMM70 seminal vesicle glandular cells Medium Enhanced O94826 +ENSG00000154174 TOMM70 testis cells in seminiferous ducts Medium Enhanced O94826 +ENSG00000154174 TOMM70 testis Leydig cells Low Enhanced O94826 +ENSG00000154188 ANGPT1 epididymis glandular cells Medium Enhanced Q15389 +ENSG00000154188 ANGPT1 seminal vesicle glandular cells Medium Enhanced Q15389 +ENSG00000154188 ANGPT1 testis cells in seminiferous ducts Low Enhanced Q15389 +ENSG00000154188 ANGPT1 testis Leydig cells Low Enhanced Q15389 +ENSG00000154229 PRKCA epididymis glandular cells Medium Enhanced P17252 +ENSG00000154229 PRKCA prostate glandular cells Low Enhanced P17252 +ENSG00000154229 PRKCA seminal vesicle glandular cells Low Enhanced P17252 +ENSG00000154229 PRKCA testis cells in seminiferous ducts Low Enhanced P17252 +ENSG00000154229 PRKCA testis Leydig cells Low Enhanced P17252 +ENSG00000154269 ENPP3 seminal vesicle glandular cells High Enhanced O14638 +ENSG00000154274 C4orf19 prostate glandular cells Low Enhanced Q8IY42 +ENSG00000154274 C4orf19 testis cells in seminiferous ducts Low Enhanced Q8IY42 +ENSG00000154274 C4orf19 testis Leydig cells Low Enhanced Q8IY42 +ENSG00000154277 UCHL1 testis cells in seminiferous ducts Low Enhanced P09936 +ENSG00000154277 UCHL1 testis Leydig cells Low Enhanced P09936 +ENSG00000154305 MIA3 epididymis glandular cells Medium Enhanced Q5JRA6 +ENSG00000154305 MIA3 prostate glandular cells Medium Enhanced Q5JRA6 +ENSG00000154305 MIA3 seminal vesicle glandular cells Low Enhanced Q5JRA6 +ENSG00000154305 MIA3 testis cells in seminiferous ducts High Enhanced Q5JRA6 +ENSG00000154305 MIA3 testis Leydig cells Low Enhanced Q5JRA6 +ENSG00000154330 PGM5 prostate glandular cells Low Enhanced Q15124 +ENSG00000154358 OBSCN epididymis glandular cells Low Enhanced Q5VST9 +ENSG00000154358 OBSCN prostate glandular cells Medium Enhanced Q5VST9 +ENSG00000154358 OBSCN seminal vesicle glandular cells Low Enhanced Q5VST9 +ENSG00000154358 OBSCN testis cells in seminiferous ducts Low Enhanced Q5VST9 +ENSG00000154358 OBSCN testis Leydig cells Medium Enhanced Q5VST9 +ENSG00000154380 ENAH epididymis glandular cells High Enhanced Q8N8S7 +ENSG00000154380 ENAH prostate glandular cells Medium Enhanced Q8N8S7 +ENSG00000154380 ENAH seminal vesicle glandular cells High Enhanced Q8N8S7 +ENSG00000154380 ENAH testis cells in seminiferous ducts High Enhanced Q8N8S7 +ENSG00000154380 ENAH testis Leydig cells High Enhanced Q8N8S7 +ENSG00000154438 ASZ1 testis elongated or late spermatids High Enhanced Q8WWH4 +ENSG00000154438 ASZ1 testis Leydig cells Low Enhanced Q8WWH4 +ENSG00000154438 ASZ1 testis pachytene spermatocytes High Enhanced Q8WWH4 +ENSG00000154438 ASZ1 testis preleptotene spermatocytes Medium Enhanced Q8WWH4 +ENSG00000154438 ASZ1 testis round or early spermatids High Enhanced Q8WWH4 +ENSG00000154438 ASZ1 testis spermatogonia Medium Enhanced Q8WWH4 +ENSG00000154473 BUB3 epididymis glandular cells Medium Supported O43684 +ENSG00000154473 BUB3 prostate glandular cells Medium Supported O43684 +ENSG00000154473 BUB3 seminal vesicle glandular cells Medium Supported O43684 +ENSG00000154473 BUB3 testis cells in seminiferous ducts Medium Supported O43684 +ENSG00000154473 BUB3 testis Leydig cells Medium Supported O43684 +ENSG00000154556 SORBS2 epididymis glandular cells Medium Supported O94875 +ENSG00000154556 SORBS2 prostate glandular cells Medium Supported O94875 +ENSG00000154556 SORBS2 seminal vesicle glandular cells Medium Supported O94875 +ENSG00000154556 SORBS2 testis cells in seminiferous ducts Low Supported O94875 +ENSG00000154556 SORBS2 testis Leydig cells Medium Supported O94875 +ENSG00000154639 CXADR epididymis glandular cells Low Enhanced P78310 +ENSG00000154639 CXADR prostate glandular cells High Enhanced P78310 +ENSG00000154639 CXADR seminal vesicle glandular cells Medium Enhanced P78310 +ENSG00000154639 CXADR testis cells in seminiferous ducts High Enhanced P78310 +ENSG00000154639 CXADR testis Leydig cells Low Enhanced P78310 +ENSG00000154645 CHODL testis elongated or late spermatids High Enhanced Q9H9P2 +ENSG00000154645 CHODL testis Leydig cells Low Enhanced Q9H9P2 +ENSG00000154645 CHODL testis pachytene spermatocytes Low Enhanced Q9H9P2 +ENSG00000154645 CHODL testis preleptotene spermatocytes High Enhanced Q9H9P2 +ENSG00000154645 CHODL testis spermatogonia Medium Enhanced Q9H9P2 +ENSG00000154654 NCAM2 testis cells in seminiferous ducts Low Supported O15394 +ENSG00000154723 ATP5J epididymis glandular cells High Supported P18859 +ENSG00000154723 ATP5J prostate glandular cells High Supported P18859 +ENSG00000154723 ATP5J seminal vesicle glandular cells High Supported P18859 +ENSG00000154723 ATP5J testis cells in seminiferous ducts High Supported P18859 +ENSG00000154723 ATP5J testis Leydig cells High Supported P18859 +ENSG00000154727 GABPA epididymis glandular cells Medium Supported Q06546 +ENSG00000154727 GABPA prostate glandular cells Low Supported Q06546 +ENSG00000154727 GABPA seminal vesicle glandular cells Low Supported Q06546 +ENSG00000154727 GABPA testis cells in seminiferous ducts Medium Supported Q06546 +ENSG00000154727 GABPA testis Leydig cells Low Supported Q06546 +ENSG00000154767 XPC epididymis glandular cells Medium Supported Q01831 +ENSG00000154767 XPC prostate glandular cells Low Supported Q01831 +ENSG00000154767 XPC seminal vesicle glandular cells Medium Supported Q01831 +ENSG00000154767 XPC testis cells in seminiferous ducts Medium Supported Q01831 +ENSG00000154767 XPC testis Leydig cells Medium Supported Q01831 +ENSG00000154803 FLCN epididymis glandular cells Medium Supported Q8NFG4 +ENSG00000154803 FLCN prostate glandular cells Medium Supported Q8NFG4 +ENSG00000154803 FLCN seminal vesicle glandular cells Medium Supported Q8NFG4 +ENSG00000154803 FLCN testis cells in seminiferous ducts Medium Supported Q8NFG4 +ENSG00000154803 FLCN testis Leydig cells Medium Supported Q8NFG4 +ENSG00000154832 CXXC1 epididymis glandular cells High Supported Q9P0U4 +ENSG00000154832 CXXC1 prostate glandular cells High Supported Q9P0U4 +ENSG00000154832 CXXC1 seminal vesicle glandular cells Medium Supported Q9P0U4 +ENSG00000154832 CXXC1 testis cells in seminiferous ducts High Supported Q9P0U4 +ENSG00000154832 CXXC1 testis Leydig cells Medium Supported Q9P0U4 +ENSG00000154864 PIEZO2 epididymis glandular cells Low Enhanced Q9H5I5 +ENSG00000154864 PIEZO2 prostate glandular cells Medium Enhanced Q9H5I5 +ENSG00000154864 PIEZO2 seminal vesicle glandular cells Low Enhanced Q9H5I5 +ENSG00000154864 PIEZO2 testis cells in seminiferous ducts Low Enhanced Q9H5I5 +ENSG00000154864 PIEZO2 testis Leydig cells Medium Enhanced Q9H5I5 +ENSG00000154920 EME1 epididymis glandular cells Medium Supported Q96AY2 +ENSG00000154920 EME1 prostate glandular cells High Supported Q96AY2 +ENSG00000154920 EME1 seminal vesicle glandular cells High Supported Q96AY2 +ENSG00000154920 EME1 testis Leydig cells Medium Supported Q96AY2 +ENSG00000154920 EME1 testis pachytene spermatocytes High Supported Q96AY2 +ENSG00000154920 EME1 testis preleptotene spermatocytes High Supported Q96AY2 +ENSG00000154920 EME1 testis round or early spermatids High Supported Q96AY2 +ENSG00000154920 EME1 testis spermatogonia Medium Supported Q96AY2 +ENSG00000154928 EPHB1 testis elongated or late spermatids Low Enhanced P54762 +ENSG00000154928 EPHB1 testis Leydig cells Low Enhanced P54762 +ENSG00000154928 EPHB1 testis pachytene spermatocytes Low Enhanced P54762 +ENSG00000154928 EPHB1 testis preleptotene spermatocytes High Enhanced P54762 +ENSG00000154928 EPHB1 testis round or early spermatids Low Enhanced P54762 +ENSG00000154928 EPHB1 testis spermatogonia High Enhanced P54762 +ENSG00000154930 ACSS1 epididymis glandular cells Low Enhanced Q9NUB1 +ENSG00000154930 ACSS1 prostate glandular cells Medium Enhanced Q9NUB1 +ENSG00000154930 ACSS1 seminal vesicle glandular cells Medium Enhanced Q9NUB1 +ENSG00000154930 ACSS1 testis cells in seminiferous ducts Medium Enhanced Q9NUB1 +ENSG00000154930 ACSS1 testis Leydig cells High Enhanced Q9NUB1 +ENSG00000154997 SEPT14 testis cells in seminiferous ducts Medium Enhanced Q6ZU15 +ENSG00000155008 APOOL prostate glandular cells Medium Enhanced Q6UXV4 +ENSG00000155008 APOOL seminal vesicle glandular cells Medium Enhanced Q6UXV4 +ENSG00000155008 APOOL testis Leydig cells Medium Enhanced Q6UXV4 +ENSG00000155026 RSPH10B testis elongated or late spermatids High Supported P0C881 +ENSG00000155026 RSPH10B testis pachytene spermatocytes Low Supported P0C881 +ENSG00000155026 RSPH10B testis round or early spermatids Medium Supported P0C881 +ENSG00000155066 PROM2 epididymis glandular cells High Enhanced Q8N271 +ENSG00000155066 PROM2 prostate glandular cells Medium Enhanced Q8N271 +ENSG00000155066 PROM2 seminal vesicle glandular cells Medium Enhanced Q8N271 +ENSG00000155085 AK9 epididymis glandular cells High Enhanced Q5TCS8 +ENSG00000155085 AK9 prostate glandular cells High Enhanced Q5TCS8 +ENSG00000155085 AK9 seminal vesicle glandular cells Medium Enhanced Q5TCS8 +ENSG00000155085 AK9 testis Leydig cells High Enhanced Q5TCS8 +ENSG00000155085 AK9 testis peritubular cells High Enhanced Q5TCS8 +ENSG00000155085 AK9 testis sertoli cells Low Enhanced Q5TCS8 +ENSG00000155100 OTUD6B epididymis glandular cells Medium Enhanced Q8N6M0 +ENSG00000155100 OTUD6B prostate glandular cells Medium Enhanced Q8N6M0 +ENSG00000155100 OTUD6B seminal vesicle glandular cells Medium Enhanced Q8N6M0 +ENSG00000155100 OTUD6B testis cells in seminiferous ducts Medium Enhanced Q8N6M0 +ENSG00000155100 OTUD6B testis Leydig cells Medium Enhanced Q8N6M0 +ENSG00000155324 GRAMD3 epididymis glandular cells Low Enhanced Q96HH9 +ENSG00000155324 GRAMD3 prostate glandular cells Low Enhanced Q96HH9 +ENSG00000155324 GRAMD3 seminal vesicle glandular cells Low Enhanced Q96HH9 +ENSG00000155324 GRAMD3 testis cells in seminiferous ducts Low Enhanced Q96HH9 +ENSG00000155324 GRAMD3 testis Leydig cells Low Enhanced Q96HH9 +ENSG00000155380 SLC16A1 epididymis glandular cells High Enhanced NA +ENSG00000155380 SLC16A1 prostate glandular cells High Enhanced NA +ENSG00000155380 SLC16A1 testis cells in seminiferous ducts High Enhanced NA +ENSG00000155380 SLC16A1 testis Leydig cells Low Enhanced NA +ENSG00000155438 NIFK epididymis glandular cells Medium Supported Q9BYG3 +ENSG00000155438 NIFK prostate glandular cells Low Supported Q9BYG3 +ENSG00000155438 NIFK seminal vesicle glandular cells Low Supported Q9BYG3 +ENSG00000155438 NIFK testis cells in seminiferous ducts Medium Supported Q9BYG3 +ENSG00000155438 NIFK testis Leydig cells Medium Supported Q9BYG3 +ENSG00000155465 SLC7A7 testis cells in seminiferous ducts Low Enhanced Q9UM01 +ENSG00000155495 MAGEC1 testis preleptotene spermatocytes Medium Enhanced O60732 +ENSG00000155495 MAGEC1 testis spermatogonia High Enhanced O60732 +ENSG00000155506 LARP1 epididymis glandular cells Low Supported Q6PKG0 +ENSG00000155506 LARP1 prostate glandular cells Low Supported Q6PKG0 +ENSG00000155506 LARP1 seminal vesicle glandular cells Medium Supported Q6PKG0 +ENSG00000155506 LARP1 testis cells in seminiferous ducts Medium Supported Q6PKG0 +ENSG00000155506 LARP1 testis Leydig cells Medium Supported Q6PKG0 +ENSG00000155660 PDIA4 epididymis glandular cells High Supported P13667 +ENSG00000155660 PDIA4 prostate glandular cells High Supported P13667 +ENSG00000155660 PDIA4 seminal vesicle glandular cells Medium Supported P13667 +ENSG00000155660 PDIA4 testis cells in seminiferous ducts High Supported P13667 +ENSG00000155660 PDIA4 testis Leydig cells Medium Supported P13667 +ENSG00000155755 TMEM237 epididymis glandular cells Medium Enhanced Q96Q45 +ENSG00000155755 TMEM237 prostate glandular cells Low Enhanced Q96Q45 +ENSG00000155755 TMEM237 seminal vesicle glandular cells Low Enhanced Q96Q45 +ENSG00000155755 TMEM237 testis cells in seminiferous ducts Low Enhanced Q96Q45 +ENSG00000155761 SPAG17 testis elongated or late spermatids Medium Enhanced Q6Q759 +ENSG00000155761 SPAG17 testis round or early spermatids Medium Enhanced Q6Q759 +ENSG00000155792 DEPTOR epididymis glandular cells Low Enhanced Q8TB45 +ENSG00000155792 DEPTOR prostate glandular cells Low Enhanced Q8TB45 +ENSG00000155792 DEPTOR testis cells in seminiferous ducts Low Enhanced Q8TB45 +ENSG00000155792 DEPTOR testis Leydig cells Medium Enhanced Q8TB45 +ENSG00000155827 RNF20 epididymis glandular cells Medium Supported Q5VTR2 +ENSG00000155827 RNF20 prostate glandular cells Medium Supported Q5VTR2 +ENSG00000155827 RNF20 seminal vesicle glandular cells Medium Supported Q5VTR2 +ENSG00000155827 RNF20 testis cells in seminiferous ducts High Supported Q5VTR2 +ENSG00000155827 RNF20 testis Leydig cells Medium Supported Q5VTR2 +ENSG00000155850 SLC26A2 epididymis glandular cells Low Enhanced P50443 +ENSG00000155850 SLC26A2 seminal vesicle glandular cells Low Enhanced P50443 +ENSG00000155875 SAXO1 testis cells in seminiferous ducts Medium Enhanced Q8IYX7 +ENSG00000155875 SAXO1 testis Leydig cells Low Enhanced Q8IYX7 +ENSG00000155876 RRAGA epididymis glandular cells Medium Supported Q7L523 +ENSG00000155876 RRAGA prostate glandular cells Medium Supported Q7L523 +ENSG00000155876 RRAGA seminal vesicle glandular cells Medium Supported Q7L523 +ENSG00000155876 RRAGA testis cells in seminiferous ducts Low Supported Q7L523 +ENSG00000155876 RRAGA testis Leydig cells Medium Supported Q7L523 +ENSG00000155897 ADCY8 epididymis glandular cells Medium Supported P40145 +ENSG00000155897 ADCY8 prostate glandular cells Medium Supported P40145 +ENSG00000155897 ADCY8 seminal vesicle glandular cells Medium Supported P40145 +ENSG00000155897 ADCY8 testis cells in seminiferous ducts Medium Supported P40145 +ENSG00000155897 ADCY8 testis Leydig cells Low Supported P40145 +ENSG00000155975 VPS37A epididymis glandular cells Medium Enhanced Q8NEZ2 +ENSG00000155975 VPS37A prostate glandular cells Low Enhanced Q8NEZ2 +ENSG00000155975 VPS37A seminal vesicle glandular cells Medium Enhanced Q8NEZ2 +ENSG00000155975 VPS37A testis cells in seminiferous ducts High Enhanced Q8NEZ2 +ENSG00000155975 VPS37A testis Leydig cells Medium Enhanced Q8NEZ2 +ENSG00000155980 KIF5A prostate glandular cells Low Enhanced Q12840 +ENSG00000155980 KIF5A seminal vesicle glandular cells Low Enhanced Q12840 +ENSG00000155980 KIF5A testis Leydig cells Low Enhanced Q12840 +ENSG00000156009 MAGEA8 testis cells in seminiferous ducts High Enhanced P43361 +ENSG00000156009 MAGEA8 testis Leydig cells High Enhanced P43361 +ENSG00000156042 CFAP70 testis cells in seminiferous ducts Medium Enhanced Q5T0N1 +ENSG00000156096 UGT2B4 testis Leydig cells Low Enhanced P06133 +ENSG00000156171 DRAM2 epididymis glandular cells Low Enhanced Q6UX65 +ENSG00000156171 DRAM2 prostate glandular cells High Enhanced Q6UX65 +ENSG00000156171 DRAM2 seminal vesicle glandular cells Low Enhanced Q6UX65 +ENSG00000156171 DRAM2 testis cells in seminiferous ducts Medium Enhanced Q6UX65 +ENSG00000156171 DRAM2 testis Leydig cells Medium Enhanced Q6UX65 +ENSG00000156219 ART3 testis elongated or late spermatids High Enhanced Q13508 +ENSG00000156219 ART3 testis Leydig cells Low Enhanced Q13508 +ENSG00000156219 ART3 testis pachytene spermatocytes High Enhanced Q13508 +ENSG00000156219 ART3 testis preleptotene spermatocytes Low Enhanced Q13508 +ENSG00000156219 ART3 testis round or early spermatids High Enhanced Q13508 +ENSG00000156219 ART3 testis spermatogonia Low Enhanced Q13508 +ENSG00000156232 WHAMM epididymis glandular cells Low Supported Q8TF30 +ENSG00000156232 WHAMM prostate glandular cells Low Supported Q8TF30 +ENSG00000156232 WHAMM seminal vesicle glandular cells Low Supported Q8TF30 +ENSG00000156232 WHAMM testis cells in seminiferous ducts Medium Supported Q8TF30 +ENSG00000156232 WHAMM testis Leydig cells Low Supported Q8TF30 +ENSG00000156256 USP16 epididymis glandular cells Medium Supported Q9Y5T5 +ENSG00000156256 USP16 prostate glandular cells Medium Supported Q9Y5T5 +ENSG00000156256 USP16 seminal vesicle glandular cells Medium Supported Q9Y5T5 +ENSG00000156256 USP16 testis cells in seminiferous ducts High Supported Q9Y5T5 +ENSG00000156256 USP16 testis Leydig cells Medium Supported Q9Y5T5 +ENSG00000156261 CCT8 epididymis glandular cells Medium Enhanced P50990 +ENSG00000156261 CCT8 prostate glandular cells Medium Enhanced P50990 +ENSG00000156261 CCT8 seminal vesicle glandular cells Medium Enhanced P50990 +ENSG00000156261 CCT8 testis cells in seminiferous ducts High Enhanced P50990 +ENSG00000156261 CCT8 testis Leydig cells Low Enhanced P50990 +ENSG00000156284 CLDN8 epididymis glandular cells High Supported P56748 +ENSG00000156284 CLDN8 prostate glandular cells High Supported P56748 +ENSG00000156284 CLDN8 seminal vesicle glandular cells High Supported P56748 +ENSG00000156284 CLDN8 testis cells in seminiferous ducts Low Supported P56748 +ENSG00000156304 SCAF4 epididymis glandular cells High Enhanced O95104 +ENSG00000156304 SCAF4 prostate glandular cells Medium Enhanced O95104 +ENSG00000156304 SCAF4 seminal vesicle glandular cells Medium Enhanced O95104 +ENSG00000156304 SCAF4 testis cells in seminiferous ducts High Enhanced O95104 +ENSG00000156304 SCAF4 testis Leydig cells Medium Enhanced O95104 +ENSG00000156345 CDK20 epididymis glandular cells Medium Enhanced Q8IZL9 +ENSG00000156345 CDK20 prostate glandular cells Low Enhanced Q8IZL9 +ENSG00000156345 CDK20 seminal vesicle glandular cells Medium Enhanced Q8IZL9 +ENSG00000156345 CDK20 testis cells in seminiferous ducts Medium Enhanced Q8IZL9 +ENSG00000156345 CDK20 testis Leydig cells Medium Enhanced Q8IZL9 +ENSG00000156398 SFXN2 epididymis glandular cells Medium Enhanced Q96NB2 +ENSG00000156398 SFXN2 prostate glandular cells Medium Enhanced Q96NB2 +ENSG00000156398 SFXN2 seminal vesicle glandular cells Medium Enhanced Q96NB2 +ENSG00000156398 SFXN2 testis Leydig cells Medium Enhanced Q96NB2 +ENSG00000156411 C14orf2 epididymis glandular cells High Enhanced P56378 +ENSG00000156411 C14orf2 prostate glandular cells High Enhanced P56378 +ENSG00000156411 C14orf2 seminal vesicle glandular cells High Enhanced P56378 +ENSG00000156411 C14orf2 testis cells in seminiferous ducts Medium Enhanced P56378 +ENSG00000156411 C14orf2 testis Leydig cells High Enhanced P56378 +ENSG00000156453 PCDH1 epididymis glandular cells Low Enhanced Q08174 +ENSG00000156453 PCDH1 prostate glandular cells Medium Enhanced Q08174 +ENSG00000156453 PCDH1 seminal vesicle glandular cells Medium Enhanced Q08174 +ENSG00000156453 PCDH1 testis cells in seminiferous ducts Low Enhanced Q08174 +ENSG00000156453 PCDH1 testis Leydig cells Medium Enhanced Q08174 +ENSG00000156502 SUPV3L1 epididymis glandular cells Medium Enhanced Q8IYB8 +ENSG00000156502 SUPV3L1 prostate glandular cells High Enhanced Q8IYB8 +ENSG00000156502 SUPV3L1 seminal vesicle glandular cells Medium Enhanced Q8IYB8 +ENSG00000156502 SUPV3L1 testis cells in seminiferous ducts High Enhanced Q8IYB8 +ENSG00000156502 SUPV3L1 testis Leydig cells High Enhanced Q8IYB8 +ENSG00000156504 FAM122B epididymis glandular cells Low Enhanced Q7Z309 +ENSG00000156504 FAM122B prostate glandular cells Medium Enhanced Q7Z309 +ENSG00000156504 FAM122B seminal vesicle glandular cells Low Enhanced Q7Z309 +ENSG00000156504 FAM122B testis cells in seminiferous ducts High Enhanced Q7Z309 +ENSG00000156504 FAM122B testis Leydig cells Medium Enhanced Q7Z309 +ENSG00000156508 EEF1A1 epididymis glandular cells High Supported P68104 +ENSG00000156508 EEF1A1 prostate glandular cells Medium Supported P68104 +ENSG00000156508 EEF1A1 seminal vesicle glandular cells High Supported P68104 +ENSG00000156508 EEF1A1 testis cells in seminiferous ducts Medium Supported P68104 +ENSG00000156508 EEF1A1 testis Leydig cells Medium Supported P68104 +ENSG00000156515 HK1 epididymis glandular cells Medium Supported P19367 +ENSG00000156515 HK1 prostate glandular cells Medium Supported P19367 +ENSG00000156515 HK1 seminal vesicle glandular cells High Supported P19367 +ENSG00000156515 HK1 testis cells in seminiferous ducts Low Supported P19367 +ENSG00000156515 HK1 testis Leydig cells Medium Supported P19367 +ENSG00000156531 PHF6 epididymis glandular cells High Enhanced Q8IWS0 +ENSG00000156531 PHF6 seminal vesicle glandular cells Medium Enhanced Q8IWS0 +ENSG00000156531 PHF6 testis cells in seminiferous ducts Medium Enhanced Q8IWS0 +ENSG00000156531 PHF6 testis Leydig cells High Enhanced Q8IWS0 +ENSG00000156587 UBE2L6 epididymis glandular cells Medium Enhanced O14933 +ENSG00000156587 UBE2L6 prostate glandular cells Medium Enhanced O14933 +ENSG00000156587 UBE2L6 seminal vesicle glandular cells Medium Enhanced O14933 +ENSG00000156587 UBE2L6 testis Leydig cells Medium Enhanced O14933 +ENSG00000156650 KAT6B epididymis glandular cells High Supported NA +ENSG00000156650 KAT6B prostate glandular cells High Supported NA +ENSG00000156650 KAT6B seminal vesicle glandular cells Medium Supported NA +ENSG00000156650 KAT6B testis cells in seminiferous ducts High Supported NA +ENSG00000156650 KAT6B testis Leydig cells High Supported NA +ENSG00000156675 RAB11FIP1 epididymis glandular cells Medium Enhanced Q6WKZ4 +ENSG00000156675 RAB11FIP1 prostate glandular cells Medium Enhanced Q6WKZ4 +ENSG00000156675 RAB11FIP1 seminal vesicle glandular cells Medium Enhanced Q6WKZ4 +ENSG00000156675 RAB11FIP1 testis cells in seminiferous ducts Medium Enhanced Q6WKZ4 +ENSG00000156675 RAB11FIP1 testis Leydig cells Medium Enhanced Q6WKZ4 +ENSG00000156709 AIFM1 epididymis glandular cells High Enhanced O95831 +ENSG00000156709 AIFM1 prostate glandular cells Medium Enhanced O95831 +ENSG00000156709 AIFM1 seminal vesicle glandular cells High Enhanced O95831 +ENSG00000156709 AIFM1 testis cells in seminiferous ducts High Enhanced O95831 +ENSG00000156709 AIFM1 testis Leydig cells High Enhanced O95831 +ENSG00000156711 MAPK13 epididymis glandular cells Medium Enhanced O15264 +ENSG00000156711 MAPK13 prostate glandular cells Medium Enhanced O15264 +ENSG00000156711 MAPK13 seminal vesicle glandular cells Medium Enhanced O15264 +ENSG00000156711 MAPK13 testis cells in seminiferous ducts Medium Enhanced O15264 +ENSG00000156711 MAPK13 testis Leydig cells Low Enhanced O15264 +ENSG00000156802 ATAD2 epididymis glandular cells Medium Enhanced Q6PL18 +ENSG00000156802 ATAD2 seminal vesicle glandular cells Low Enhanced Q6PL18 +ENSG00000156802 ATAD2 testis cells in seminiferous ducts High Enhanced Q6PL18 +ENSG00000156831 NSMCE2 epididymis glandular cells High Supported Q96MF7 +ENSG00000156831 NSMCE2 prostate glandular cells Medium Supported Q96MF7 +ENSG00000156831 NSMCE2 seminal vesicle glandular cells Medium Supported Q96MF7 +ENSG00000156831 NSMCE2 testis cells in seminiferous ducts High Supported Q96MF7 +ENSG00000156831 NSMCE2 testis Leydig cells High Supported Q96MF7 +ENSG00000156966 B3GNT7 seminal vesicle glandular cells Low Enhanced Q8NFL0 +ENSG00000156983 BRPF1 epididymis glandular cells Medium Enhanced P55201 +ENSG00000156983 BRPF1 prostate glandular cells Low Enhanced P55201 +ENSG00000156983 BRPF1 seminal vesicle glandular cells Low Enhanced P55201 +ENSG00000156983 BRPF1 testis cells in seminiferous ducts Medium Enhanced P55201 +ENSG00000156983 BRPF1 testis Leydig cells Low Enhanced P55201 +ENSG00000157036 EXOG epididymis glandular cells Medium Enhanced Q9Y2C4 +ENSG00000157036 EXOG prostate glandular cells Low Enhanced Q9Y2C4 +ENSG00000157036 EXOG seminal vesicle glandular cells Low Enhanced Q9Y2C4 +ENSG00000157036 EXOG testis cells in seminiferous ducts High Enhanced Q9Y2C4 +ENSG00000157036 EXOG testis Leydig cells High Enhanced Q9Y2C4 +ENSG00000157060 SHCBP1L testis elongated or late spermatids High Enhanced Q9BZQ2 +ENSG00000157060 SHCBP1L testis Leydig cells Medium Enhanced Q9BZQ2 +ENSG00000157060 SHCBP1L testis pachytene spermatocytes High Enhanced Q9BZQ2 +ENSG00000157060 SHCBP1L testis round or early spermatids High Enhanced Q9BZQ2 +ENSG00000157064 NMNAT2 testis cells in seminiferous ducts Low Enhanced Q9BZQ4 +ENSG00000157064 NMNAT2 testis Leydig cells Low Enhanced Q9BZQ4 +ENSG00000157107 FCHO2 epididymis glandular cells Medium Enhanced Q0JRZ9 +ENSG00000157107 FCHO2 prostate glandular cells Medium Enhanced Q0JRZ9 +ENSG00000157107 FCHO2 seminal vesicle glandular cells Low Enhanced Q0JRZ9 +ENSG00000157107 FCHO2 testis cells in seminiferous ducts Medium Enhanced Q0JRZ9 +ENSG00000157107 FCHO2 testis Leydig cells Low Enhanced Q0JRZ9 +ENSG00000157110 RBPMS prostate glandular cells Low Enhanced Q93062 +ENSG00000157110 RBPMS seminal vesicle glandular cells Low Enhanced Q93062 +ENSG00000157110 RBPMS testis Leydig cells Medium Enhanced Q93062 +ENSG00000157184 CPT2 epididymis glandular cells Low Enhanced P23786 +ENSG00000157184 CPT2 prostate glandular cells Low Enhanced P23786 +ENSG00000157184 CPT2 seminal vesicle glandular cells Medium Enhanced P23786 +ENSG00000157184 CPT2 testis cells in seminiferous ducts Medium Enhanced P23786 +ENSG00000157184 CPT2 testis Leydig cells High Enhanced P23786 +ENSG00000157193 LRP8 testis cells in seminiferous ducts High Enhanced Q14114 +ENSG00000157212 PAXIP1 epididymis glandular cells High Enhanced Q6ZW49 +ENSG00000157212 PAXIP1 prostate glandular cells High Enhanced Q6ZW49 +ENSG00000157212 PAXIP1 seminal vesicle glandular cells High Enhanced Q6ZW49 +ENSG00000157212 PAXIP1 testis cells in seminiferous ducts High Enhanced Q6ZW49 +ENSG00000157212 PAXIP1 testis Leydig cells High Enhanced Q6ZW49 +ENSG00000157423 HYDIN testis elongated or late spermatids Medium Enhanced NA +ENSG00000157423 HYDIN testis preleptotene spermatocytes Low Enhanced NA +ENSG00000157423 HYDIN testis round or early spermatids Low Enhanced NA +ENSG00000157423 HYDIN testis spermatogonia Low Enhanced NA +ENSG00000157450 RNF111 epididymis glandular cells Medium Enhanced Q6ZNA4 +ENSG00000157450 RNF111 prostate glandular cells Medium Enhanced Q6ZNA4 +ENSG00000157450 RNF111 seminal vesicle glandular cells Medium Enhanced Q6ZNA4 +ENSG00000157450 RNF111 testis cells in seminiferous ducts High Enhanced Q6ZNA4 +ENSG00000157450 RNF111 testis Leydig cells High Enhanced Q6ZNA4 +ENSG00000157456 CCNB2 epididymis glandular cells Low Enhanced O95067 +ENSG00000157456 CCNB2 prostate glandular cells Low Enhanced O95067 +ENSG00000157456 CCNB2 seminal vesicle glandular cells Low Enhanced O95067 +ENSG00000157456 CCNB2 testis Leydig cells High Enhanced O95067 +ENSG00000157456 CCNB2 testis pachytene spermatocytes High Enhanced O95067 +ENSG00000157456 CCNB2 testis peritubular cells Medium Enhanced O95067 +ENSG00000157456 CCNB2 testis preleptotene spermatocytes Medium Enhanced O95067 +ENSG00000157456 CCNB2 testis spermatogonia Low Enhanced O95067 +ENSG00000157470 FAM81A epididymis glandular cells Medium Enhanced Q8TBF8 +ENSG00000157470 FAM81A prostate glandular cells Low Enhanced Q8TBF8 +ENSG00000157470 FAM81A seminal vesicle glandular cells Low Enhanced Q8TBF8 +ENSG00000157470 FAM81A testis cells in seminiferous ducts Medium Enhanced Q8TBF8 +ENSG00000157470 FAM81A testis Leydig cells Low Enhanced Q8TBF8 +ENSG00000157502 MUM1L1 epididymis glandular cells Medium Enhanced Q5H9M0 +ENSG00000157502 MUM1L1 prostate glandular cells Low Enhanced Q5H9M0 +ENSG00000157502 MUM1L1 testis cells in seminiferous ducts Medium Enhanced Q5H9M0 +ENSG00000157502 MUM1L1 testis Leydig cells Low Enhanced Q5H9M0 +ENSG00000157578 LCA5L testis cells in seminiferous ducts Medium Enhanced O95447 +ENSG00000157578 LCA5L testis Leydig cells Medium Enhanced O95447 +ENSG00000157613 CREB3L1 epididymis glandular cells Medium Enhanced Q96BA8 +ENSG00000157613 CREB3L1 prostate glandular cells Medium Enhanced Q96BA8 +ENSG00000157613 CREB3L1 seminal vesicle glandular cells Medium Enhanced Q96BA8 +ENSG00000157613 CREB3L1 testis cells in seminiferous ducts Medium Enhanced Q96BA8 +ENSG00000157613 CREB3L1 testis Leydig cells Medium Enhanced Q96BA8 +ENSG00000157617 C2CD2 epididymis glandular cells High Enhanced Q9Y426 +ENSG00000157617 C2CD2 prostate glandular cells Medium Enhanced Q9Y426 +ENSG00000157617 C2CD2 seminal vesicle glandular cells Medium Enhanced Q9Y426 +ENSG00000157617 C2CD2 testis cells in seminiferous ducts Medium Enhanced Q9Y426 +ENSG00000157617 C2CD2 testis Leydig cells Medium Enhanced Q9Y426 +ENSG00000157637 SLC38A10 epididymis glandular cells High Enhanced Q9HBR0 +ENSG00000157637 SLC38A10 prostate glandular cells High Enhanced Q9HBR0 +ENSG00000157637 SLC38A10 seminal vesicle glandular cells High Enhanced Q9HBR0 +ENSG00000157637 SLC38A10 testis cells in seminiferous ducts Medium Enhanced Q9HBR0 +ENSG00000157637 SLC38A10 testis Leydig cells Medium Enhanced Q9HBR0 +ENSG00000157765 SLC34A2 seminal vesicle glandular cells Low Enhanced O95436 +ENSG00000157851 DPYSL5 testis elongated or late spermatids Medium Enhanced Q9BPU6 +ENSG00000157851 DPYSL5 testis pachytene spermatocytes Low Enhanced Q9BPU6 +ENSG00000157851 DPYSL5 testis round or early spermatids Medium Enhanced Q9BPU6 +ENSG00000157916 RER1 epididymis glandular cells High Supported O15258 +ENSG00000157916 RER1 prostate glandular cells Medium Supported O15258 +ENSG00000157916 RER1 seminal vesicle glandular cells Medium Supported O15258 +ENSG00000157916 RER1 testis cells in seminiferous ducts High Supported O15258 +ENSG00000157916 RER1 testis Leydig cells Medium Supported O15258 +ENSG00000157992 KRTCAP3 epididymis glandular cells Medium Enhanced Q53RY4 +ENSG00000157992 KRTCAP3 prostate glandular cells High Enhanced Q53RY4 +ENSG00000157992 KRTCAP3 seminal vesicle glandular cells Medium Enhanced Q53RY4 +ENSG00000157992 KRTCAP3 testis cells in seminiferous ducts Medium Enhanced Q53RY4 +ENSG00000158023 WDR66 epididymis glandular cells Medium Supported Q8TBY9 +ENSG00000158023 WDR66 prostate glandular cells Medium Supported Q8TBY9 +ENSG00000158023 WDR66 seminal vesicle glandular cells Medium Supported Q8TBY9 +ENSG00000158023 WDR66 testis cells in seminiferous ducts Medium Supported Q8TBY9 +ENSG00000158023 WDR66 testis Leydig cells Medium Supported Q8TBY9 +ENSG00000158055 GRHL3 epididymis glandular cells Medium Enhanced Q8TE85 +ENSG00000158055 GRHL3 prostate glandular cells Medium Enhanced Q8TE85 +ENSG00000158055 GRHL3 seminal vesicle glandular cells Low Enhanced Q8TE85 +ENSG00000158055 GRHL3 testis cells in seminiferous ducts Low Enhanced Q8TE85 +ENSG00000158055 GRHL3 testis Leydig cells Medium Enhanced Q8TE85 +ENSG00000158092 NCK1 epididymis glandular cells Medium Supported P16333 +ENSG00000158092 NCK1 prostate glandular cells High Supported P16333 +ENSG00000158092 NCK1 seminal vesicle glandular cells High Supported P16333 +ENSG00000158092 NCK1 testis cells in seminiferous ducts High Supported P16333 +ENSG00000158092 NCK1 testis Leydig cells High Supported P16333 +ENSG00000158158 CNNM4 epididymis glandular cells Medium Enhanced Q6P4Q7 +ENSG00000158158 CNNM4 prostate glandular cells Medium Enhanced Q6P4Q7 +ENSG00000158158 CNNM4 seminal vesicle glandular cells Medium Enhanced Q6P4Q7 +ENSG00000158158 CNNM4 testis cells in seminiferous ducts Low Enhanced Q6P4Q7 +ENSG00000158195 WASF2 epididymis glandular cells Medium Enhanced Q9Y6W5 +ENSG00000158195 WASF2 prostate glandular cells Medium Enhanced Q9Y6W5 +ENSG00000158195 WASF2 seminal vesicle glandular cells Medium Enhanced Q9Y6W5 +ENSG00000158195 WASF2 testis cells in seminiferous ducts Medium Enhanced Q9Y6W5 +ENSG00000158195 WASF2 testis Leydig cells Medium Enhanced Q9Y6W5 +ENSG00000158290 CUL4B epididymis glandular cells High Enhanced Q13620 +ENSG00000158290 CUL4B prostate glandular cells Low Enhanced Q13620 +ENSG00000158290 CUL4B seminal vesicle glandular cells Medium Enhanced Q13620 +ENSG00000158290 CUL4B testis cells in seminiferous ducts Medium Enhanced Q13620 +ENSG00000158290 CUL4B testis Leydig cells High Enhanced Q13620 +ENSG00000158301 GPRASP2 epididymis glandular cells Low Enhanced Q96D09 +ENSG00000158301 GPRASP2 prostate glandular cells Medium Enhanced Q96D09 +ENSG00000158301 GPRASP2 seminal vesicle glandular cells Low Enhanced Q96D09 +ENSG00000158301 GPRASP2 testis cells in seminiferous ducts High Enhanced Q96D09 +ENSG00000158301 GPRASP2 testis Leydig cells Low Enhanced Q96D09 +ENSG00000158373 HIST1H2BD epididymis glandular cells High Supported P58876 +ENSG00000158373 HIST1H2BD prostate glandular cells High Supported P58876 +ENSG00000158373 HIST1H2BD seminal vesicle glandular cells High Supported P58876 +ENSG00000158373 HIST1H2BD testis cells in seminiferous ducts High Supported P58876 +ENSG00000158373 HIST1H2BD testis Leydig cells High Supported P58876 +ENSG00000158406 HIST1H4H epididymis glandular cells Low Supported NA +ENSG00000158406 HIST1H4H prostate glandular cells Low Supported NA +ENSG00000158406 HIST1H4H seminal vesicle glandular cells Medium Supported NA +ENSG00000158406 HIST1H4H testis cells in seminiferous ducts Medium Supported NA +ENSG00000158428 CATIP testis Leydig cells Low Supported Q7Z7H3 +ENSG00000158545 ZC3H18 epididymis glandular cells High Enhanced Q86VM9 +ENSG00000158545 ZC3H18 prostate glandular cells High Enhanced Q86VM9 +ENSG00000158545 ZC3H18 seminal vesicle glandular cells High Enhanced Q86VM9 +ENSG00000158545 ZC3H18 testis cells in seminiferous ducts High Enhanced Q86VM9 +ENSG00000158545 ZC3H18 testis Leydig cells High Enhanced Q86VM9 +ENSG00000158560 DYNC1I1 epididymis glandular cells Low Enhanced O14576 +ENSG00000158560 DYNC1I1 seminal vesicle glandular cells Low Enhanced O14576 +ENSG00000158636 EMSY epididymis glandular cells High Supported Q7Z589 +ENSG00000158636 EMSY prostate glandular cells High Supported Q7Z589 +ENSG00000158636 EMSY seminal vesicle glandular cells High Supported Q7Z589 +ENSG00000158636 EMSY testis cells in seminiferous ducts Medium Supported Q7Z589 +ENSG00000158636 EMSY testis Leydig cells Medium Supported Q7Z589 +ENSG00000158639 PAGE5 testis cells in seminiferous ducts Low Supported Q96GU1 +ENSG00000158715 SLC45A3 prostate glandular cells High Enhanced Q96JT2 +ENSG00000158769 F11R epididymis glandular cells Low Enhanced Q9Y624 +ENSG00000158769 F11R prostate glandular cells Medium Enhanced Q9Y624 +ENSG00000158769 F11R seminal vesicle glandular cells High Enhanced Q9Y624 +ENSG00000158769 F11R testis Leydig cells High Enhanced Q9Y624 +ENSG00000158773 USF1 epididymis glandular cells Medium Supported P22415 +ENSG00000158773 USF1 prostate glandular cells Medium Supported P22415 +ENSG00000158773 USF1 seminal vesicle glandular cells Medium Supported P22415 +ENSG00000158773 USF1 testis cells in seminiferous ducts Low Supported P22415 +ENSG00000158773 USF1 testis Leydig cells Medium Supported P22415 +ENSG00000158806 NPM2 prostate glandular cells Low Enhanced Q86SE8 +ENSG00000158806 NPM2 testis Leydig cells High Enhanced Q86SE8 +ENSG00000158816 VWA5B1 testis elongated or late spermatids High Enhanced Q5TIE3 +ENSG00000158816 VWA5B1 testis Leydig cells Low Enhanced Q5TIE3 +ENSG00000158816 VWA5B1 testis pachytene spermatocytes Medium Enhanced Q5TIE3 +ENSG00000158816 VWA5B1 testis peritubular cells Low Enhanced Q5TIE3 +ENSG00000158816 VWA5B1 testis preleptotene spermatocytes Low Enhanced Q5TIE3 +ENSG00000158816 VWA5B1 testis round or early spermatids High Enhanced Q5TIE3 +ENSG00000158816 VWA5B1 testis spermatogonia Low Enhanced Q5TIE3 +ENSG00000158864 NDUFS2 seminal vesicle glandular cells Medium Enhanced O75306 +ENSG00000158864 NDUFS2 testis Leydig cells Medium Enhanced O75306 +ENSG00000158869 FCER1G epididymis glandular cells Low Supported P30273 +ENSG00000158869 FCER1G prostate glandular cells Low Supported P30273 +ENSG00000158869 FCER1G testis Leydig cells Low Supported P30273 +ENSG00000158887 MPZ testis cells in seminiferous ducts Low Supported P25189 +ENSG00000158941 CCAR2 epididymis glandular cells High Enhanced Q8N163 +ENSG00000158941 CCAR2 prostate glandular cells High Enhanced Q8N163 +ENSG00000158941 CCAR2 seminal vesicle glandular cells Medium Enhanced Q8N163 +ENSG00000158941 CCAR2 testis cells in seminiferous ducts High Enhanced Q8N163 +ENSG00000158941 CCAR2 testis Leydig cells Medium Enhanced Q8N163 +ENSG00000158985 CDC42SE2 epididymis glandular cells High Enhanced Q9NRR3 +ENSG00000158985 CDC42SE2 prostate glandular cells Medium Enhanced Q9NRR3 +ENSG00000158985 CDC42SE2 seminal vesicle glandular cells Low Enhanced Q9NRR3 +ENSG00000158985 CDC42SE2 testis cells in seminiferous ducts Medium Enhanced Q9NRR3 +ENSG00000159055 MIS18A epididymis glandular cells Low Enhanced Q9NYP9 +ENSG00000159055 MIS18A prostate glandular cells Low Enhanced Q9NYP9 +ENSG00000159055 MIS18A seminal vesicle glandular cells Low Enhanced Q9NYP9 +ENSG00000159055 MIS18A testis cells in seminiferous ducts High Enhanced Q9NYP9 +ENSG00000159055 MIS18A testis Leydig cells Medium Enhanced Q9NYP9 +ENSG00000159079 C21orf59 epididymis glandular cells Medium Enhanced P57076 +ENSG00000159079 C21orf59 prostate glandular cells Medium Enhanced P57076 +ENSG00000159079 C21orf59 seminal vesicle glandular cells Low Enhanced P57076 +ENSG00000159079 C21orf59 testis cells in seminiferous ducts High Enhanced P57076 +ENSG00000159079 C21orf59 testis Leydig cells Low Enhanced P57076 +ENSG00000159082 SYNJ1 epididymis glandular cells Medium Enhanced O43426 +ENSG00000159082 SYNJ1 prostate glandular cells Low Enhanced O43426 +ENSG00000159082 SYNJ1 seminal vesicle glandular cells Low Enhanced O43426 +ENSG00000159082 SYNJ1 testis cells in seminiferous ducts Medium Enhanced O43426 +ENSG00000159082 SYNJ1 testis Leydig cells Low Enhanced O43426 +ENSG00000159111 MRPL10 epididymis glandular cells Medium Enhanced Q7Z7H8 +ENSG00000159111 MRPL10 prostate glandular cells Medium Enhanced Q7Z7H8 +ENSG00000159111 MRPL10 seminal vesicle glandular cells Medium Enhanced Q7Z7H8 +ENSG00000159111 MRPL10 testis cells in seminiferous ducts Low Enhanced Q7Z7H8 +ENSG00000159111 MRPL10 testis Leydig cells Medium Enhanced Q7Z7H8 +ENSG00000159128 IFNGR2 epididymis glandular cells Low Enhanced B5MCZ0 +ENSG00000159128 IFNGR2 prostate glandular cells Medium Enhanced B5MCZ0 +ENSG00000159128 IFNGR2 seminal vesicle glandular cells Medium Enhanced B5MCZ0 +ENSG00000159128 IFNGR2 testis cells in seminiferous ducts Medium Enhanced B5MCZ0 +ENSG00000159128 IFNGR2 testis Leydig cells Medium Enhanced B5MCZ0 +ENSG00000159140 SON epididymis glandular cells Medium Supported P18583 +ENSG00000159140 SON prostate glandular cells Medium Supported P18583 +ENSG00000159140 SON seminal vesicle glandular cells Medium Supported P18583 +ENSG00000159140 SON testis cells in seminiferous ducts Medium Supported P18583 +ENSG00000159140 SON testis Leydig cells Medium Supported P18583 +ENSG00000159164 SV2A epididymis glandular cells Low Enhanced Q7L0J3 +ENSG00000159166 LAD1 epididymis glandular cells Low Enhanced O00515 +ENSG00000159166 LAD1 prostate glandular cells Low Enhanced O00515 +ENSG00000159166 LAD1 seminal vesicle glandular cells Medium Enhanced O00515 +ENSG00000159184 HOXB13 prostate glandular cells High Enhanced Q92826 +ENSG00000159189 C1QC prostate glandular cells Medium Supported P02747 +ENSG00000159189 C1QC testis Leydig cells Low Supported P02747 +ENSG00000159208 CIART epididymis glandular cells Medium Enhanced Q8N365 +ENSG00000159208 CIART prostate glandular cells Medium Enhanced Q8N365 +ENSG00000159208 CIART seminal vesicle glandular cells Medium Enhanced Q8N365 +ENSG00000159208 CIART testis cells in seminiferous ducts Low Enhanced Q8N365 +ENSG00000159208 CIART testis Leydig cells Low Enhanced Q8N365 +ENSG00000159216 RUNX1 epididymis glandular cells Low Enhanced Q01196 +ENSG00000159216 RUNX1 prostate glandular cells Low Enhanced Q01196 +ENSG00000159216 RUNX1 testis cells in seminiferous ducts Low Enhanced Q01196 +ENSG00000159216 RUNX1 testis Leydig cells Low Enhanced Q01196 +ENSG00000159217 IGF2BP1 testis elongated or late spermatids Low Enhanced Q9NZI8 +ENSG00000159217 IGF2BP1 testis pachytene spermatocytes Low Enhanced Q9NZI8 +ENSG00000159217 IGF2BP1 testis preleptotene spermatocytes High Enhanced Q9NZI8 +ENSG00000159217 IGF2BP1 testis round or early spermatids Low Enhanced Q9NZI8 +ENSG00000159217 IGF2BP1 testis spermatogonia High Enhanced Q9NZI8 +ENSG00000159259 CHAF1B testis cells in seminiferous ducts Medium Enhanced Q13112 +ENSG00000159289 GOLGA6A testis elongated or late spermatids High Supported Q9NYA3 +ENSG00000159289 GOLGA6A testis round or early spermatids High Supported Q9NYA3 +ENSG00000159289 GOLGA6A testis spermatogonia High Supported Q9NYA3 +ENSG00000159348 CYB5R1 epididymis glandular cells High Enhanced Q9UHQ9 +ENSG00000159348 CYB5R1 prostate glandular cells Medium Enhanced Q9UHQ9 +ENSG00000159348 CYB5R1 seminal vesicle glandular cells Medium Enhanced Q9UHQ9 +ENSG00000159348 CYB5R1 testis cells in seminiferous ducts Medium Enhanced Q9UHQ9 +ENSG00000159348 CYB5R1 testis Leydig cells High Enhanced Q9UHQ9 +ENSG00000159352 PSMD4 epididymis glandular cells Medium Enhanced P55036 +ENSG00000159352 PSMD4 prostate glandular cells Low Enhanced P55036 +ENSG00000159352 PSMD4 seminal vesicle glandular cells Low Enhanced P55036 +ENSG00000159352 PSMD4 testis cells in seminiferous ducts High Enhanced P55036 +ENSG00000159352 PSMD4 testis Leydig cells High Enhanced P55036 +ENSG00000159399 HK2 epididymis glandular cells High Enhanced P52789 +ENSG00000159399 HK2 prostate glandular cells Low Enhanced P52789 +ENSG00000159399 HK2 seminal vesicle glandular cells Low Enhanced P52789 +ENSG00000159399 HK2 testis cells in seminiferous ducts Medium Enhanced P52789 +ENSG00000159399 HK2 testis Leydig cells Medium Enhanced P52789 +ENSG00000159423 ALDH4A1 epididymis glandular cells High Enhanced P30038 +ENSG00000159423 ALDH4A1 prostate glandular cells High Enhanced P30038 +ENSG00000159423 ALDH4A1 testis cells in seminiferous ducts High Enhanced P30038 +ENSG00000159423 ALDH4A1 testis Leydig cells High Enhanced P30038 +ENSG00000159593 NAE1 epididymis glandular cells High Enhanced Q13564 +ENSG00000159593 NAE1 prostate glandular cells High Enhanced Q13564 +ENSG00000159593 NAE1 seminal vesicle glandular cells Medium Enhanced Q13564 +ENSG00000159593 NAE1 testis cells in seminiferous ducts High Enhanced Q13564 +ENSG00000159593 NAE1 testis Leydig cells High Enhanced Q13564 +ENSG00000159618 ADGRG5 testis cells in seminiferous ducts Low Enhanced Q8IZF4 +ENSG00000159640 ACE epididymis glandular cells Medium Enhanced P12821 +ENSG00000159640 ACE prostate glandular cells Medium Enhanced P12821 +ENSG00000159640 ACE seminal vesicle glandular cells Medium Enhanced P12821 +ENSG00000159640 ACE testis cells in seminiferous ducts Medium Enhanced P12821 +ENSG00000159648 TEPP testis cells in seminiferous ducts High Enhanced Q6URK8 +ENSG00000159658 EFCAB14 epididymis glandular cells Medium Supported O75071 +ENSG00000159658 EFCAB14 prostate glandular cells Medium Supported O75071 +ENSG00000159658 EFCAB14 seminal vesicle glandular cells High Supported O75071 +ENSG00000159658 EFCAB14 testis cells in seminiferous ducts High Supported O75071 +ENSG00000159658 EFCAB14 testis Leydig cells Medium Supported O75071 +ENSG00000159708 LRRC36 testis elongated or late spermatids High Enhanced Q1X8D7 +ENSG00000159708 LRRC36 testis pachytene spermatocytes Low Enhanced Q1X8D7 +ENSG00000159708 LRRC36 testis round or early spermatids Medium Enhanced Q1X8D7 +ENSG00000159761 C16orf86 testis cells in seminiferous ducts Medium Enhanced Q6ZW13 +ENSG00000159763 PIP seminal vesicle glandular cells Low Enhanced P12273 +ENSG00000159842 ABR epididymis glandular cells High Enhanced A0A0D9SGD7 +ENSG00000159842 ABR prostate glandular cells High Enhanced A0A0D9SGD7 +ENSG00000159842 ABR seminal vesicle glandular cells Medium Enhanced A0A0D9SGD7 +ENSG00000159842 ABR testis cells in seminiferous ducts Medium Enhanced A0A0D9SGD7 +ENSG00000159842 ABR testis Leydig cells Medium Enhanced A0A0D9SGD7 +ENSG00000160049 DFFA epididymis glandular cells Medium Supported O00273 +ENSG00000160049 DFFA prostate glandular cells Medium Supported O00273 +ENSG00000160049 DFFA seminal vesicle glandular cells Medium Supported O00273 +ENSG00000160049 DFFA testis cells in seminiferous ducts Medium Supported O00273 +ENSG00000160049 DFFA testis Leydig cells Low Supported O00273 +ENSG00000160075 SSU72 epididymis glandular cells Medium Enhanced Q9NP77 +ENSG00000160075 SSU72 prostate glandular cells Medium Enhanced Q9NP77 +ENSG00000160075 SSU72 seminal vesicle glandular cells Medium Enhanced Q9NP77 +ENSG00000160075 SSU72 testis cells in seminiferous ducts Medium Enhanced Q9NP77 +ENSG00000160075 SSU72 testis Leydig cells High Enhanced Q9NP77 +ENSG00000160188 RSPH1 testis cells in seminiferous ducts Medium Enhanced Q8WYR4 +ENSG00000160191 PDE9A epididymis glandular cells High Enhanced O76083 +ENSG00000160191 PDE9A prostate glandular cells Medium Enhanced O76083 +ENSG00000160191 PDE9A seminal vesicle glandular cells Medium Enhanced O76083 +ENSG00000160191 PDE9A testis Leydig cells Low Enhanced O76083 +ENSG00000160194 NDUFV3 epididymis glandular cells Low Enhanced P56181 +ENSG00000160194 NDUFV3 prostate glandular cells High Enhanced P56181 +ENSG00000160194 NDUFV3 seminal vesicle glandular cells High Enhanced P56181 +ENSG00000160194 NDUFV3 testis cells in seminiferous ducts Medium Enhanced P56181 +ENSG00000160194 NDUFV3 testis Leydig cells Medium Enhanced P56181 +ENSG00000160201 U2AF1 epididymis glandular cells High Supported Q01081 +ENSG00000160201 U2AF1 prostate glandular cells Medium Supported Q01081 +ENSG00000160201 U2AF1 seminal vesicle glandular cells High Supported Q01081 +ENSG00000160201 U2AF1 testis cells in seminiferous ducts High Supported Q01081 +ENSG00000160201 U2AF1 testis Leydig cells High Supported Q01081 +ENSG00000160208 RRP1B epididymis glandular cells Medium Supported Q14684 +ENSG00000160208 RRP1B prostate glandular cells Medium Supported Q14684 +ENSG00000160208 RRP1B seminal vesicle glandular cells Medium Supported Q14684 +ENSG00000160208 RRP1B testis cells in seminiferous ducts High Supported Q14684 +ENSG00000160208 RRP1B testis Leydig cells Low Supported Q14684 +ENSG00000160211 G6PD epididymis glandular cells Medium Enhanced P11413 +ENSG00000160211 G6PD prostate glandular cells Medium Enhanced P11413 +ENSG00000160211 G6PD seminal vesicle glandular cells Medium Enhanced P11413 +ENSG00000160211 G6PD testis cells in seminiferous ducts High Enhanced P11413 +ENSG00000160211 G6PD testis Leydig cells Medium Enhanced P11413 +ENSG00000160218 TRAPPC10 epididymis glandular cells Low Supported P48553 +ENSG00000160218 TRAPPC10 seminal vesicle glandular cells Medium Supported P48553 +ENSG00000160218 TRAPPC10 testis Leydig cells Low Supported P48553 +ENSG00000160221 C21orf33 epididymis glandular cells Medium Supported P30042 +ENSG00000160221 C21orf33 prostate glandular cells High Supported P30042 +ENSG00000160221 C21orf33 seminal vesicle glandular cells Medium Supported P30042 +ENSG00000160221 C21orf33 testis cells in seminiferous ducts Medium Supported P30042 +ENSG00000160221 C21orf33 testis Leydig cells Medium Supported P30042 +ENSG00000160226 C21orf2 epididymis glandular cells Medium Supported O43822 +ENSG00000160226 C21orf2 prostate glandular cells Medium Supported O43822 +ENSG00000160226 C21orf2 seminal vesicle glandular cells Medium Supported O43822 +ENSG00000160226 C21orf2 testis cells in seminiferous ducts Medium Supported O43822 +ENSG00000160226 C21orf2 testis Leydig cells Medium Supported O43822 +ENSG00000160285 LSS epididymis glandular cells Medium Supported P48449 +ENSG00000160285 LSS prostate glandular cells Medium Supported P48449 +ENSG00000160285 LSS seminal vesicle glandular cells Low Supported P48449 +ENSG00000160285 LSS testis cells in seminiferous ducts Medium Supported P48449 +ENSG00000160285 LSS testis Leydig cells High Supported P48449 +ENSG00000160299 PCNT epididymis glandular cells Low Enhanced O95613 +ENSG00000160299 PCNT seminal vesicle glandular cells Medium Enhanced O95613 +ENSG00000160299 PCNT testis cells in seminiferous ducts Medium Enhanced O95613 +ENSG00000160299 PCNT testis Leydig cells Low Enhanced O95613 +ENSG00000160469 BRSK1 epididymis glandular cells Low Supported Q8TDC3 +ENSG00000160469 BRSK1 prostate glandular cells Low Supported Q8TDC3 +ENSG00000160469 BRSK1 testis cells in seminiferous ducts Low Supported Q8TDC3 +ENSG00000160469 BRSK1 testis Leydig cells Medium Supported Q8TDC3 +ENSG00000160584 SIK3 epididymis glandular cells High Enhanced Q9Y2K2 +ENSG00000160584 SIK3 prostate glandular cells High Enhanced Q9Y2K2 +ENSG00000160584 SIK3 seminal vesicle glandular cells High Enhanced Q9Y2K2 +ENSG00000160584 SIK3 testis cells in seminiferous ducts High Enhanced Q9Y2K2 +ENSG00000160584 SIK3 testis Leydig cells High Enhanced Q9Y2K2 +ENSG00000160606 TLCD1 epididymis glandular cells Medium Enhanced Q96CP7 +ENSG00000160606 TLCD1 prostate glandular cells Low Enhanced Q96CP7 +ENSG00000160606 TLCD1 seminal vesicle glandular cells High Enhanced Q96CP7 +ENSG00000160606 TLCD1 testis cells in seminiferous ducts Medium Enhanced Q96CP7 +ENSG00000160606 TLCD1 testis Leydig cells Medium Enhanced Q96CP7 +ENSG00000160633 SAFB epididymis glandular cells High Supported Q15424 +ENSG00000160633 SAFB prostate glandular cells High Supported Q15424 +ENSG00000160633 SAFB seminal vesicle glandular cells High Supported Q15424 +ENSG00000160633 SAFB testis cells in seminiferous ducts High Supported Q15424 +ENSG00000160633 SAFB testis Leydig cells High Supported Q15424 +ENSG00000160678 S100A1 epididymis glandular cells Low Enhanced P23297 +ENSG00000160678 S100A1 seminal vesicle glandular cells Low Enhanced P23297 +ENSG00000160678 S100A1 testis cells in seminiferous ducts Low Enhanced P23297 +ENSG00000160678 S100A1 testis Leydig cells Low Enhanced P23297 +ENSG00000160683 CXCR5 epididymis glandular cells Medium Enhanced P32302 +ENSG00000160683 CXCR5 testis cells in seminiferous ducts Medium Enhanced P32302 +ENSG00000160683 CXCR5 testis Leydig cells Medium Enhanced P32302 +ENSG00000160685 ZBTB7B prostate glandular cells Medium Enhanced O15156 +ENSG00000160685 ZBTB7B seminal vesicle glandular cells Low Enhanced O15156 +ENSG00000160685 ZBTB7B testis Leydig cells Low Enhanced O15156 +ENSG00000160691 SHC1 epididymis glandular cells High Supported P29353 +ENSG00000160691 SHC1 prostate glandular cells Medium Supported P29353 +ENSG00000160691 SHC1 seminal vesicle glandular cells High Supported P29353 +ENSG00000160691 SHC1 testis cells in seminiferous ducts Medium Supported P29353 +ENSG00000160691 SHC1 testis Leydig cells Medium Supported P29353 +ENSG00000160703 NLRX1 epididymis glandular cells Medium Supported Q86UT6 +ENSG00000160703 NLRX1 prostate glandular cells Medium Supported Q86UT6 +ENSG00000160703 NLRX1 seminal vesicle glandular cells Medium Supported Q86UT6 +ENSG00000160703 NLRX1 testis cells in seminiferous ducts Medium Supported Q86UT6 +ENSG00000160703 NLRX1 testis Leydig cells High Supported Q86UT6 +ENSG00000160710 ADAR epididymis glandular cells Medium Enhanced P55265 +ENSG00000160710 ADAR prostate glandular cells Medium Enhanced P55265 +ENSG00000160710 ADAR seminal vesicle glandular cells Medium Enhanced P55265 +ENSG00000160710 ADAR testis cells in seminiferous ducts High Enhanced P55265 +ENSG00000160710 ADAR testis Leydig cells Medium Enhanced P55265 +ENSG00000160741 CRTC2 epididymis glandular cells Medium Supported Q53ET0 +ENSG00000160741 CRTC2 prostate glandular cells High Supported Q53ET0 +ENSG00000160741 CRTC2 seminal vesicle glandular cells Medium Supported Q53ET0 +ENSG00000160741 CRTC2 testis cells in seminiferous ducts Medium Supported Q53ET0 +ENSG00000160741 CRTC2 testis Leydig cells Medium Supported Q53ET0 +ENSG00000160789 LMNA epididymis glandular cells High Supported P02545 +ENSG00000160789 LMNA prostate glandular cells High Supported P02545 +ENSG00000160789 LMNA seminal vesicle glandular cells High Supported P02545 +ENSG00000160789 LMNA testis cells in seminiferous ducts High Supported P02545 +ENSG00000160789 LMNA testis Leydig cells High Supported P02545 +ENSG00000160813 PPP1R35 prostate glandular cells Low Enhanced Q8TAP8 +ENSG00000160813 PPP1R35 testis Leydig cells High Enhanced Q8TAP8 +ENSG00000160862 AZGP1 prostate glandular cells High Enhanced P25311 +ENSG00000160877 NACC1 epididymis glandular cells High Supported Q96RE7 +ENSG00000160877 NACC1 prostate glandular cells Low Supported Q96RE7 +ENSG00000160877 NACC1 seminal vesicle glandular cells Medium Supported Q96RE7 +ENSG00000160877 NACC1 testis cells in seminiferous ducts High Supported Q96RE7 +ENSG00000160877 NACC1 testis Leydig cells High Supported Q96RE7 +ENSG00000160886 LY6K testis elongated or late spermatids Low Enhanced Q17RY6 +ENSG00000160886 LY6K testis pachytene spermatocytes High Enhanced Q17RY6 +ENSG00000160886 LY6K testis round or early spermatids Low Enhanced Q17RY6 +ENSG00000160948 VPS28 epididymis glandular cells Medium Enhanced Q9UK41 +ENSG00000160948 VPS28 prostate glandular cells High Enhanced Q9UK41 +ENSG00000160948 VPS28 seminal vesicle glandular cells Low Enhanced Q9UK41 +ENSG00000160948 VPS28 testis cells in seminiferous ducts High Enhanced Q9UK41 +ENSG00000160957 RECQL4 epididymis glandular cells Low Supported O94761 +ENSG00000160957 RECQL4 prostate glandular cells Low Supported O94761 +ENSG00000160957 RECQL4 seminal vesicle glandular cells Low Supported O94761 +ENSG00000160957 RECQL4 testis cells in seminiferous ducts Low Supported O94761 +ENSG00000160957 RECQL4 testis Leydig cells Medium Supported O94761 +ENSG00000161011 SQSTM1 epididymis glandular cells Medium Supported Q13501 +ENSG00000161011 SQSTM1 prostate glandular cells Medium Supported Q13501 +ENSG00000161011 SQSTM1 seminal vesicle glandular cells Medium Supported Q13501 +ENSG00000161011 SQSTM1 testis cells in seminiferous ducts Medium Supported Q13501 +ENSG00000161011 SQSTM1 testis Leydig cells High Supported Q13501 +ENSG00000161016 RPL8 epididymis glandular cells Medium Enhanced P62917 +ENSG00000161016 RPL8 prostate glandular cells Medium Enhanced P62917 +ENSG00000161016 RPL8 seminal vesicle glandular cells Medium Enhanced P62917 +ENSG00000161016 RPL8 testis cells in seminiferous ducts Medium Enhanced P62917 +ENSG00000161016 RPL8 testis Leydig cells Medium Enhanced P62917 +ENSG00000161036 LRWD1 testis elongated or late spermatids Medium Enhanced Q9UFC0 +ENSG00000161036 LRWD1 testis Leydig cells Low Enhanced Q9UFC0 +ENSG00000161036 LRWD1 testis pachytene spermatocytes High Enhanced Q9UFC0 +ENSG00000161036 LRWD1 testis preleptotene spermatocytes Medium Enhanced Q9UFC0 +ENSG00000161036 LRWD1 testis round or early spermatids High Enhanced Q9UFC0 +ENSG00000161036 LRWD1 testis spermatogonia High Enhanced Q9UFC0 +ENSG00000161057 PSMC2 epididymis glandular cells Medium Supported P35998 +ENSG00000161057 PSMC2 prostate glandular cells Medium Supported P35998 +ENSG00000161057 PSMC2 seminal vesicle glandular cells Medium Supported P35998 +ENSG00000161057 PSMC2 testis cells in seminiferous ducts High Supported P35998 +ENSG00000161057 PSMC2 testis Leydig cells High Supported P35998 +ENSG00000161265 U2AF1L4 epididymis glandular cells High Supported Q8WU68 +ENSG00000161265 U2AF1L4 prostate glandular cells Medium Supported Q8WU68 +ENSG00000161265 U2AF1L4 seminal vesicle glandular cells High Supported Q8WU68 +ENSG00000161265 U2AF1L4 testis cells in seminiferous ducts High Supported Q8WU68 +ENSG00000161265 U2AF1L4 testis Leydig cells High Supported Q8WU68 +ENSG00000161267 BDH1 epididymis glandular cells Medium Enhanced C9JB83 +ENSG00000161267 BDH1 prostate glandular cells Medium Enhanced C9JB83 +ENSG00000161267 BDH1 seminal vesicle glandular cells High Enhanced C9JB83 +ENSG00000161267 BDH1 testis cells in seminiferous ducts Medium Enhanced C9JB83 +ENSG00000161267 BDH1 testis Leydig cells High Enhanced C9JB83 +ENSG00000161513 FDXR epididymis glandular cells High Enhanced P22570 +ENSG00000161513 FDXR testis cells in seminiferous ducts High Enhanced P22570 +ENSG00000161513 FDXR testis Leydig cells High Enhanced P22570 +ENSG00000161526 SAP30BP epididymis glandular cells Medium Supported Q9UHR5 +ENSG00000161526 SAP30BP prostate glandular cells Medium Supported Q9UHR5 +ENSG00000161526 SAP30BP seminal vesicle glandular cells High Supported Q9UHR5 +ENSG00000161526 SAP30BP testis cells in seminiferous ducts High Supported Q9UHR5 +ENSG00000161526 SAP30BP testis Leydig cells High Supported Q9UHR5 +ENSG00000161547 SRSF2 epididymis glandular cells High Supported Q01130 +ENSG00000161547 SRSF2 prostate glandular cells Medium Supported Q01130 +ENSG00000161547 SRSF2 seminal vesicle glandular cells Medium Supported Q01130 +ENSG00000161547 SRSF2 testis cells in seminiferous ducts High Supported Q01130 +ENSG00000161547 SRSF2 testis Leydig cells High Supported Q01130 +ENSG00000161594 KLHL10 testis elongated or late spermatids High Enhanced Q6JEL2 +ENSG00000161594 KLHL10 testis Leydig cells Low Enhanced Q6JEL2 +ENSG00000161594 KLHL10 testis round or early spermatids High Enhanced Q6JEL2 +ENSG00000161609 CCDC155 epididymis glandular cells Medium Enhanced Q8N6L0 +ENSG00000161609 CCDC155 prostate glandular cells Medium Enhanced Q8N6L0 +ENSG00000161609 CCDC155 seminal vesicle glandular cells Medium Enhanced Q8N6L0 +ENSG00000161609 CCDC155 testis cells in seminiferous ducts Medium Enhanced Q8N6L0 +ENSG00000161609 CCDC155 testis Leydig cells Medium Enhanced Q8N6L0 +ENSG00000161798 AQP5 testis elongated or late spermatids High Enhanced P55064 +ENSG00000161798 AQP5 testis Leydig cells Medium Enhanced P55064 +ENSG00000161798 AQP5 testis pachytene spermatocytes High Enhanced P55064 +ENSG00000161798 AQP5 testis round or early spermatids High Enhanced P55064 +ENSG00000161800 RACGAP1 epididymis glandular cells Low Enhanced Q9H0H5 +ENSG00000161800 RACGAP1 testis elongated or late spermatids Medium Enhanced Q9H0H5 +ENSG00000161800 RACGAP1 testis pachytene spermatocytes High Enhanced Q9H0H5 +ENSG00000161800 RACGAP1 testis preleptotene spermatocytes Medium Enhanced Q9H0H5 +ENSG00000161800 RACGAP1 testis round or early spermatids Medium Enhanced Q9H0H5 +ENSG00000161847 RAVER1 epididymis glandular cells Medium Enhanced Q8IY67 +ENSG00000161847 RAVER1 prostate glandular cells High Enhanced Q8IY67 +ENSG00000161847 RAVER1 seminal vesicle glandular cells High Enhanced Q8IY67 +ENSG00000161847 RAVER1 testis cells in seminiferous ducts High Enhanced Q8IY67 +ENSG00000161847 RAVER1 testis Leydig cells Medium Enhanced Q8IY67 +ENSG00000161860 SYCE2 testis pachytene spermatocytes High Enhanced Q6PIF2 +ENSG00000161860 SYCE2 testis round or early spermatids Medium Enhanced Q6PIF2 +ENSG00000161904 LEMD2 epididymis glandular cells Medium Supported Q8NC56 +ENSG00000161904 LEMD2 prostate glandular cells Low Supported Q8NC56 +ENSG00000161904 LEMD2 seminal vesicle glandular cells High Supported Q8NC56 +ENSG00000161904 LEMD2 testis cells in seminiferous ducts Medium Supported Q8NC56 +ENSG00000161904 LEMD2 testis Leydig cells High Supported Q8NC56 +ENSG00000161956 SENP3 epididymis glandular cells Low Supported Q9H4L4 +ENSG00000161956 SENP3 seminal vesicle glandular cells Low Supported Q9H4L4 +ENSG00000161956 SENP3 testis cells in seminiferous ducts Medium Supported Q9H4L4 +ENSG00000161956 SENP3 testis Leydig cells Medium Supported Q9H4L4 +ENSG00000161958 FGF11 testis Leydig cells Medium Enhanced I3L4N4 +ENSG00000161970 RPL26 epididymis glandular cells Medium Supported P61254 +ENSG00000161970 RPL26 prostate glandular cells Medium Supported P61254 +ENSG00000161970 RPL26 seminal vesicle glandular cells Medium Supported P61254 +ENSG00000161970 RPL26 testis cells in seminiferous ducts Medium Supported P61254 +ENSG00000161970 RPL26 testis Leydig cells Medium Supported P61254 +ENSG00000162066 AMDHD2 epididymis glandular cells Low Enhanced Q9Y303 +ENSG00000162066 AMDHD2 testis cells in seminiferous ducts Low Enhanced Q9Y303 +ENSG00000162066 AMDHD2 testis Leydig cells Medium Enhanced Q9Y303 +ENSG00000162078 ZG16B prostate glandular cells Low Enhanced NA +ENSG00000162129 CLPB epididymis glandular cells Medium Enhanced Q9H078 +ENSG00000162129 CLPB prostate glandular cells Medium Enhanced Q9H078 +ENSG00000162129 CLPB seminal vesicle glandular cells High Enhanced Q9H078 +ENSG00000162129 CLPB testis cells in seminiferous ducts Medium Enhanced Q9H078 +ENSG00000162129 CLPB testis Leydig cells High Enhanced Q9H078 +ENSG00000162148 PPP1R32 testis elongated or late spermatids High Enhanced Q7Z5V6 +ENSG00000162148 PPP1R32 testis Leydig cells Medium Enhanced Q7Z5V6 +ENSG00000162148 PPP1R32 testis pachytene spermatocytes Medium Enhanced Q7Z5V6 +ENSG00000162148 PPP1R32 testis preleptotene spermatocytes Medium Enhanced Q7Z5V6 +ENSG00000162148 PPP1R32 testis round or early spermatids High Enhanced Q7Z5V6 +ENSG00000162148 PPP1R32 testis spermatogonia Low Enhanced Q7Z5V6 +ENSG00000162174 ASRGL1 epididymis glandular cells High Enhanced Q7L266 +ENSG00000162174 ASRGL1 prostate glandular cells Low Enhanced Q7L266 +ENSG00000162174 ASRGL1 seminal vesicle glandular cells Low Enhanced Q7L266 +ENSG00000162174 ASRGL1 testis cells in seminiferous ducts High Enhanced Q7L266 +ENSG00000162174 ASRGL1 testis Leydig cells Low Enhanced Q7L266 +ENSG00000162231 NXF1 epididymis glandular cells High Supported Q9UBU9 +ENSG00000162231 NXF1 prostate glandular cells High Supported Q9UBU9 +ENSG00000162231 NXF1 seminal vesicle glandular cells High Supported Q9UBU9 +ENSG00000162231 NXF1 testis cells in seminiferous ducts High Supported Q9UBU9 +ENSG00000162231 NXF1 testis Leydig cells High Supported Q9UBU9 +ENSG00000162298 SYVN1 epididymis glandular cells Medium Enhanced Q86TM6 +ENSG00000162298 SYVN1 prostate glandular cells Medium Enhanced Q86TM6 +ENSG00000162298 SYVN1 seminal vesicle glandular cells Low Enhanced Q86TM6 +ENSG00000162298 SYVN1 testis cells in seminiferous ducts High Enhanced Q86TM6 +ENSG00000162298 SYVN1 testis Leydig cells Medium Enhanced Q86TM6 +ENSG00000162300 ZFPL1 epididymis glandular cells Medium Enhanced O95159 +ENSG00000162300 ZFPL1 prostate glandular cells Medium Enhanced O95159 +ENSG00000162300 ZFPL1 seminal vesicle glandular cells Medium Enhanced O95159 +ENSG00000162300 ZFPL1 testis cells in seminiferous ducts Medium Enhanced O95159 +ENSG00000162300 ZFPL1 testis Leydig cells Medium Enhanced O95159 +ENSG00000162341 TPCN2 epididymis glandular cells Low Enhanced Q8NHX9 +ENSG00000162341 TPCN2 prostate glandular cells High Enhanced Q8NHX9 +ENSG00000162341 TPCN2 seminal vesicle glandular cells High Enhanced Q8NHX9 +ENSG00000162366 PDZK1IP1 epididymis glandular cells Medium Enhanced Q13113 +ENSG00000162366 PDZK1IP1 prostate glandular cells Medium Enhanced Q13113 +ENSG00000162366 PDZK1IP1 seminal vesicle glandular cells Low Enhanced Q13113 +ENSG00000162366 PDZK1IP1 testis cells in seminiferous ducts Medium Enhanced Q13113 +ENSG00000162366 PDZK1IP1 testis Leydig cells Medium Enhanced Q13113 +ENSG00000162374 ELAVL4 testis elongated or late spermatids Low Enhanced P26378 +ENSG00000162374 ELAVL4 testis pachytene spermatocytes Medium Enhanced P26378 +ENSG00000162374 ELAVL4 testis preleptotene spermatocytes High Enhanced P26378 +ENSG00000162374 ELAVL4 testis round or early spermatids Medium Enhanced P26378 +ENSG00000162374 ELAVL4 testis spermatogonia High Enhanced P26378 +ENSG00000162390 ACOT11 epididymis glandular cells Low Enhanced Q8WXI4 +ENSG00000162390 ACOT11 seminal vesicle glandular cells Low Enhanced Q8WXI4 +ENSG00000162419 GMEB1 epididymis glandular cells High Supported Q9Y692 +ENSG00000162419 GMEB1 prostate glandular cells Medium Supported Q9Y692 +ENSG00000162419 GMEB1 seminal vesicle glandular cells Medium Supported Q9Y692 +ENSG00000162419 GMEB1 testis cells in seminiferous ducts High Supported Q9Y692 +ENSG00000162419 GMEB1 testis Leydig cells Medium Supported Q9Y692 +ENSG00000162433 AK4 epididymis glandular cells Low Enhanced P27144 +ENSG00000162433 AK4 prostate glandular cells Low Enhanced P27144 +ENSG00000162433 AK4 seminal vesicle glandular cells Low Enhanced P27144 +ENSG00000162433 AK4 testis cells in seminiferous ducts Medium Enhanced P27144 +ENSG00000162433 AK4 testis Leydig cells Medium Enhanced P27144 +ENSG00000162444 RBP7 epididymis glandular cells Medium Enhanced Q96R05 +ENSG00000162444 RBP7 prostate glandular cells Medium Enhanced Q96R05 +ENSG00000162444 RBP7 seminal vesicle glandular cells Medium Enhanced Q96R05 +ENSG00000162444 RBP7 testis cells in seminiferous ducts Medium Enhanced Q96R05 +ENSG00000162444 RBP7 testis Leydig cells Medium Enhanced Q96R05 +ENSG00000162496 DHRS3 epididymis glandular cells Medium Supported O75911 +ENSG00000162496 DHRS3 prostate glandular cells Medium Supported O75911 +ENSG00000162496 DHRS3 seminal vesicle glandular cells Medium Supported O75911 +ENSG00000162496 DHRS3 testis cells in seminiferous ducts Medium Supported O75911 +ENSG00000162496 DHRS3 testis Leydig cells Medium Supported O75911 +ENSG00000162521 RBBP4 epididymis glandular cells High Enhanced Q09028 +ENSG00000162521 RBBP4 prostate glandular cells High Enhanced Q09028 +ENSG00000162521 RBBP4 seminal vesicle glandular cells High Enhanced Q09028 +ENSG00000162521 RBBP4 testis cells in seminiferous ducts High Enhanced Q09028 +ENSG00000162521 RBBP4 testis Leydig cells High Enhanced Q09028 +ENSG00000162551 ALPL epididymis glandular cells Medium Enhanced P05186 +ENSG00000162551 ALPL prostate glandular cells Low Enhanced P05186 +ENSG00000162551 ALPL seminal vesicle glandular cells Medium Enhanced P05186 +ENSG00000162551 ALPL testis cells in seminiferous ducts Low Enhanced P05186 +ENSG00000162551 ALPL testis Leydig cells Low Enhanced P05186 +ENSG00000162572 SCNN1D epididymis glandular cells Medium Enhanced P51172 +ENSG00000162572 SCNN1D seminal vesicle glandular cells Low Enhanced P51172 +ENSG00000162572 SCNN1D testis cells in seminiferous ducts Medium Enhanced P51172 +ENSG00000162572 SCNN1D testis Leydig cells Low Enhanced P51172 +ENSG00000162599 NFIA epididymis glandular cells High Enhanced Q12857 +ENSG00000162599 NFIA prostate glandular cells Medium Enhanced Q12857 +ENSG00000162599 NFIA seminal vesicle glandular cells High Enhanced Q12857 +ENSG00000162599 NFIA testis cells in seminiferous ducts Medium Enhanced Q12857 +ENSG00000162599 NFIA testis Leydig cells High Enhanced Q12857 +ENSG00000162613 FUBP1 epididymis glandular cells High Enhanced Q96AE4 +ENSG00000162613 FUBP1 prostate glandular cells High Enhanced Q96AE4 +ENSG00000162613 FUBP1 seminal vesicle glandular cells High Enhanced Q96AE4 +ENSG00000162613 FUBP1 testis cells in seminiferous ducts High Enhanced Q96AE4 +ENSG00000162613 FUBP1 testis Leydig cells Medium Enhanced Q96AE4 +ENSG00000162627 SNX7 prostate glandular cells Medium Enhanced Q9UNH6 +ENSG00000162627 SNX7 seminal vesicle glandular cells Medium Enhanced Q9UNH6 +ENSG00000162627 SNX7 testis cells in seminiferous ducts Low Enhanced Q9UNH6 +ENSG00000162627 SNX7 testis Leydig cells Medium Enhanced Q9UNH6 +ENSG00000162643 WDR63 testis elongated or late spermatids Medium Enhanced Q8IWG1 +ENSG00000162643 WDR63 testis Leydig cells Medium Enhanced Q8IWG1 +ENSG00000162643 WDR63 testis pachytene spermatocytes Low Enhanced Q8IWG1 +ENSG00000162643 WDR63 testis preleptotene spermatocytes Low Enhanced Q8IWG1 +ENSG00000162643 WDR63 testis round or early spermatids High Enhanced Q8IWG1 +ENSG00000162643 WDR63 testis spermatogonia Low Enhanced Q8IWG1 +ENSG00000162645 GBP2 epididymis glandular cells Medium Supported P32456 +ENSG00000162645 GBP2 prostate glandular cells High Supported P32456 +ENSG00000162645 GBP2 seminal vesicle glandular cells Medium Supported P32456 +ENSG00000162645 GBP2 testis cells in seminiferous ducts Low Supported P32456 +ENSG00000162645 GBP2 testis Leydig cells High Supported P32456 +ENSG00000162654 GBP4 epididymis glandular cells Low Enhanced Q96PP9 +ENSG00000162654 GBP4 prostate glandular cells Medium Enhanced Q96PP9 +ENSG00000162654 GBP4 seminal vesicle glandular cells Medium Enhanced Q96PP9 +ENSG00000162654 GBP4 testis cells in seminiferous ducts Medium Enhanced Q96PP9 +ENSG00000162654 GBP4 testis Leydig cells High Enhanced Q96PP9 +ENSG00000162664 ZNF326 epididymis glandular cells Medium Supported Q5BKZ1 +ENSG00000162664 ZNF326 prostate glandular cells Medium Supported Q5BKZ1 +ENSG00000162664 ZNF326 seminal vesicle glandular cells Low Supported Q5BKZ1 +ENSG00000162664 ZNF326 testis cells in seminiferous ducts Medium Supported Q5BKZ1 +ENSG00000162664 ZNF326 testis Leydig cells Medium Supported Q5BKZ1 +ENSG00000162734 PEA15 testis Leydig cells Low Enhanced Q15121 +ENSG00000162735 PEX19 epididymis glandular cells High Supported P40855 +ENSG00000162735 PEX19 prostate glandular cells High Supported P40855 +ENSG00000162735 PEX19 seminal vesicle glandular cells High Supported P40855 +ENSG00000162735 PEX19 testis cells in seminiferous ducts High Supported P40855 +ENSG00000162735 PEX19 testis Leydig cells Medium Supported P40855 +ENSG00000162771 FAM71A testis cells in seminiferous ducts Medium Enhanced Q8IYT1 +ENSG00000162775 RBM15 epididymis glandular cells Medium Supported Q96T37 +ENSG00000162775 RBM15 prostate glandular cells Low Supported Q96T37 +ENSG00000162775 RBM15 seminal vesicle glandular cells Low Supported Q96T37 +ENSG00000162775 RBM15 testis cells in seminiferous ducts Low Supported Q96T37 +ENSG00000162775 RBM15 testis Leydig cells Low Supported Q96T37 +ENSG00000162779 AXDND1 testis elongated or late spermatids High Enhanced Q5T1B0 +ENSG00000162779 AXDND1 testis pachytene spermatocytes High Enhanced Q5T1B0 +ENSG00000162779 AXDND1 testis preleptotene spermatocytes Low Enhanced Q5T1B0 +ENSG00000162779 AXDND1 testis round or early spermatids High Enhanced Q5T1B0 +ENSG00000162779 AXDND1 testis spermatogonia Low Enhanced Q5T1B0 +ENSG00000162782 TDRD5 testis cells in seminiferous ducts High Enhanced Q8NAT2 +ENSG00000162814 SPATA17 testis cells in seminiferous ducts High Enhanced Q96L03 +ENSG00000162849 KIF26B epididymis glandular cells Medium Enhanced Q2KJY2 +ENSG00000162849 KIF26B prostate glandular cells Medium Enhanced Q2KJY2 +ENSG00000162849 KIF26B seminal vesicle glandular cells Medium Enhanced Q2KJY2 +ENSG00000162849 KIF26B testis cells in seminiferous ducts Medium Enhanced Q2KJY2 +ENSG00000162849 KIF26B testis Leydig cells Medium Enhanced Q2KJY2 +ENSG00000162897 FCAMR prostate glandular cells Low Enhanced Q8WWV6 +ENSG00000162910 MRPL55 epididymis glandular cells High Supported Q7Z7F7 +ENSG00000162910 MRPL55 prostate glandular cells Medium Supported Q7Z7F7 +ENSG00000162910 MRPL55 seminal vesicle glandular cells High Supported Q7Z7F7 +ENSG00000162910 MRPL55 testis cells in seminiferous ducts Medium Supported Q7Z7F7 +ENSG00000162910 MRPL55 testis Leydig cells High Supported Q7Z7F7 +ENSG00000162923 WDR26 epididymis glandular cells Medium Enhanced Q9H7D7 +ENSG00000162923 WDR26 prostate glandular cells Medium Enhanced Q9H7D7 +ENSG00000162923 WDR26 seminal vesicle glandular cells Medium Enhanced Q9H7D7 +ENSG00000162923 WDR26 testis cells in seminiferous ducts Medium Enhanced Q9H7D7 +ENSG00000162923 WDR26 testis Leydig cells Low Enhanced Q9H7D7 +ENSG00000162928 PEX13 epididymis glandular cells Medium Enhanced Q92968 +ENSG00000162928 PEX13 prostate glandular cells Medium Enhanced Q92968 +ENSG00000162928 PEX13 seminal vesicle glandular cells High Enhanced Q92968 +ENSG00000162928 PEX13 testis cells in seminiferous ducts High Enhanced Q92968 +ENSG00000162928 PEX13 testis Leydig cells Medium Enhanced Q92968 +ENSG00000162961 DPY30 epididymis glandular cells Medium Supported Q9C005 +ENSG00000162961 DPY30 prostate glandular cells Medium Supported Q9C005 +ENSG00000162961 DPY30 seminal vesicle glandular cells Medium Supported Q9C005 +ENSG00000162961 DPY30 testis cells in seminiferous ducts Medium Supported Q9C005 +ENSG00000162961 DPY30 testis Leydig cells Medium Supported Q9C005 +ENSG00000163002 NUP35 epididymis glandular cells Medium Enhanced Q8NFH5 +ENSG00000163002 NUP35 prostate glandular cells Low Enhanced Q8NFH5 +ENSG00000163002 NUP35 seminal vesicle glandular cells Low Enhanced Q8NFH5 +ENSG00000163002 NUP35 testis cells in seminiferous ducts Medium Enhanced Q8NFH5 +ENSG00000163002 NUP35 testis Leydig cells Medium Enhanced Q8NFH5 +ENSG00000163006 CCDC138 epididymis glandular cells Low Enhanced Q96M89 +ENSG00000163006 CCDC138 testis elongated or late spermatids Medium Enhanced Q96M89 +ENSG00000163006 CCDC138 testis Leydig cells Low Enhanced Q96M89 +ENSG00000163006 CCDC138 testis pachytene spermatocytes Medium Enhanced Q96M89 +ENSG00000163006 CCDC138 testis peritubular cells Low Enhanced Q96M89 +ENSG00000163006 CCDC138 testis preleptotene spermatocytes Medium Enhanced Q96M89 +ENSG00000163006 CCDC138 testis round or early spermatids Medium Enhanced Q96M89 +ENSG00000163006 CCDC138 testis spermatogonia High Enhanced Q96M89 +ENSG00000163017 ACTG2 epididymis glandular cells Medium Supported P63267 +ENSG00000163017 ACTG2 testis cells in seminiferous ducts Low Supported P63267 +ENSG00000163041 H3F3A epididymis glandular cells High Supported B4DEB1 +ENSG00000163041 H3F3A prostate glandular cells High Supported B4DEB1 +ENSG00000163041 H3F3A seminal vesicle glandular cells High Supported B4DEB1 +ENSG00000163041 H3F3A testis cells in seminiferous ducts High Supported B4DEB1 +ENSG00000163041 H3F3A testis Leydig cells High Supported B4DEB1 +ENSG00000163071 SPATA18 epididymis glandular cells Low Enhanced Q8TC71 +ENSG00000163071 SPATA18 testis elongated or late spermatids High Enhanced Q8TC71 +ENSG00000163071 SPATA18 testis Leydig cells Medium Enhanced Q8TC71 +ENSG00000163071 SPATA18 testis pachytene spermatocytes Low Enhanced Q8TC71 +ENSG00000163071 SPATA18 testis round or early spermatids Low Enhanced Q8TC71 +ENSG00000163131 CTSS epididymis glandular cells Low Supported P25774 +ENSG00000163131 CTSS testis cells in seminiferous ducts Low Supported P25774 +ENSG00000163131 CTSS testis Leydig cells Low Supported P25774 +ENSG00000163166 IWS1 epididymis glandular cells Medium Enhanced Q96ST2 +ENSG00000163166 IWS1 prostate glandular cells Medium Enhanced Q96ST2 +ENSG00000163166 IWS1 testis cells in seminiferous ducts Medium Enhanced Q96ST2 +ENSG00000163166 IWS1 testis Leydig cells Medium Enhanced Q96ST2 +ENSG00000163191 S100A11 epididymis glandular cells Medium Enhanced P31949 +ENSG00000163191 S100A11 prostate glandular cells High Enhanced P31949 +ENSG00000163191 S100A11 seminal vesicle glandular cells High Enhanced P31949 +ENSG00000163206 SMCP testis elongated or late spermatids High Supported P49901 +ENSG00000163206 SMCP testis Leydig cells Low Supported P49901 +ENSG00000163206 SMCP testis peritubular cells Medium Supported P49901 +ENSG00000163207 IVL epididymis glandular cells Medium Enhanced P07476 +ENSG00000163320 CGGBP1 epididymis glandular cells High Supported Q9UFW8 +ENSG00000163320 CGGBP1 prostate glandular cells High Supported Q9UFW8 +ENSG00000163320 CGGBP1 seminal vesicle glandular cells High Supported Q9UFW8 +ENSG00000163320 CGGBP1 testis cells in seminiferous ducts High Supported Q9UFW8 +ENSG00000163320 CGGBP1 testis Leydig cells High Supported Q9UFW8 +ENSG00000163331 DAPL1 epididymis glandular cells Medium Enhanced A0PJW8 +ENSG00000163331 DAPL1 testis cells in seminiferous ducts Medium Enhanced A0PJW8 +ENSG00000163347 CLDN1 epididymis glandular cells Medium Enhanced O95832 +ENSG00000163347 CLDN1 prostate glandular cells Medium Enhanced O95832 +ENSG00000163347 CLDN1 seminal vesicle glandular cells Medium Enhanced O95832 +ENSG00000163347 CLDN1 testis cells in seminiferous ducts Low Enhanced O95832 +ENSG00000163347 CLDN1 testis Leydig cells Low Enhanced O95832 +ENSG00000163348 PYGO2 epididymis glandular cells Medium Supported Q9BRQ0 +ENSG00000163348 PYGO2 prostate glandular cells Medium Supported Q9BRQ0 +ENSG00000163348 PYGO2 seminal vesicle glandular cells Low Supported Q9BRQ0 +ENSG00000163348 PYGO2 testis cells in seminiferous ducts Low Supported Q9BRQ0 +ENSG00000163348 PYGO2 testis Leydig cells Medium Supported Q9BRQ0 +ENSG00000163382 NAXE epididymis glandular cells Medium Enhanced Q8NCW5 +ENSG00000163382 NAXE prostate glandular cells Medium Enhanced Q8NCW5 +ENSG00000163382 NAXE seminal vesicle glandular cells Medium Enhanced Q8NCW5 +ENSG00000163382 NAXE testis cells in seminiferous ducts Medium Enhanced Q8NCW5 +ENSG00000163382 NAXE testis Leydig cells Low Enhanced Q8NCW5 +ENSG00000163399 ATP1A1 epididymis glandular cells Medium Enhanced P05023 +ENSG00000163399 ATP1A1 prostate glandular cells High Enhanced P05023 +ENSG00000163399 ATP1A1 seminal vesicle glandular cells High Enhanced P05023 +ENSG00000163399 ATP1A1 testis cells in seminiferous ducts Medium Enhanced P05023 +ENSG00000163399 ATP1A1 testis Leydig cells Low Enhanced P05023 +ENSG00000163424 C3orf30 testis elongated or late spermatids High Enhanced Q96M34 +ENSG00000163424 C3orf30 testis pachytene spermatocytes Low Enhanced Q96M34 +ENSG00000163424 C3orf30 testis round or early spermatids Medium Enhanced Q96M34 +ENSG00000163435 ELF3 seminal vesicle glandular cells Low Enhanced P78545 +ENSG00000163440 PDCL2 testis elongated or late spermatids High Enhanced Q8N4E4 +ENSG00000163440 PDCL2 testis Leydig cells Low Enhanced Q8N4E4 +ENSG00000163440 PDCL2 testis pachytene spermatocytes Low Enhanced Q8N4E4 +ENSG00000163440 PDCL2 testis round or early spermatids High Enhanced Q8N4E4 +ENSG00000163440 PDCL2 testis spermatogonia Low Enhanced Q8N4E4 +ENSG00000163472 TMEM79 prostate glandular cells High Enhanced Q9BSE2 +ENSG00000163521 GLB1L epididymis glandular cells Low Enhanced Q6UWU2 +ENSG00000163521 GLB1L testis elongated or late spermatids High Enhanced Q6UWU2 +ENSG00000163521 GLB1L testis Leydig cells Low Enhanced Q6UWU2 +ENSG00000163521 GLB1L testis pachytene spermatocytes Medium Enhanced Q6UWU2 +ENSG00000163521 GLB1L testis round or early spermatids High Enhanced Q6UWU2 +ENSG00000163531 NFASC epididymis glandular cells Low Enhanced O94856 +ENSG00000163531 NFASC seminal vesicle glandular cells Low Enhanced O94856 +ENSG00000163531 NFASC testis cells in seminiferous ducts Low Enhanced O94856 +ENSG00000163535 SGO2 testis pachytene spermatocytes High Enhanced Q562F6 +ENSG00000163541 SUCLG1 epididymis glandular cells High Enhanced P53597 +ENSG00000163541 SUCLG1 prostate glandular cells High Enhanced P53597 +ENSG00000163541 SUCLG1 seminal vesicle glandular cells High Enhanced P53597 +ENSG00000163541 SUCLG1 testis cells in seminiferous ducts High Enhanced P53597 +ENSG00000163541 SUCLG1 testis Leydig cells High Enhanced P53597 +ENSG00000163564 PYHIN1 epididymis glandular cells Medium Enhanced Q6K0P9 +ENSG00000163564 PYHIN1 prostate glandular cells Low Enhanced Q6K0P9 +ENSG00000163564 PYHIN1 testis cells in seminiferous ducts Medium Enhanced Q6K0P9 +ENSG00000163564 PYHIN1 testis Leydig cells Low Enhanced Q6K0P9 +ENSG00000163565 IFI16 epididymis glandular cells Medium Enhanced Q16666 +ENSG00000163565 IFI16 prostate glandular cells Low Enhanced Q16666 +ENSG00000163624 CDS1 epididymis glandular cells High Enhanced Q92903 +ENSG00000163624 CDS1 seminal vesicle glandular cells Low Enhanced Q92903 +ENSG00000163624 CDS1 testis cells in seminiferous ducts High Enhanced Q92903 +ENSG00000163624 CDS1 testis Leydig cells Medium Enhanced Q92903 +ENSG00000163626 COX18 epididymis glandular cells Medium Enhanced Q8N8Q8 +ENSG00000163626 COX18 prostate glandular cells Medium Enhanced Q8N8Q8 +ENSG00000163626 COX18 seminal vesicle glandular cells Low Enhanced Q8N8Q8 +ENSG00000163626 COX18 testis cells in seminiferous ducts Medium Enhanced Q8N8Q8 +ENSG00000163626 COX18 testis Leydig cells Medium Enhanced Q8N8Q8 +ENSG00000163631 ALB epididymis glandular cells Low Supported P02768 +ENSG00000163631 ALB testis cells in seminiferous ducts Medium Supported P02768 +ENSG00000163645 ERICH6 testis preleptotene spermatocytes High Enhanced Q7L0X2 +ENSG00000163645 ERICH6 testis spermatogonia High Enhanced Q7L0X2 +ENSG00000163681 SLMAP epididymis glandular cells Low Enhanced Q14BN4 +ENSG00000163681 SLMAP seminal vesicle glandular cells High Enhanced Q14BN4 +ENSG00000163681 SLMAP testis cells in seminiferous ducts High Enhanced Q14BN4 +ENSG00000163694 RBM47 epididymis glandular cells Medium Enhanced A0AV96 +ENSG00000163694 RBM47 prostate glandular cells Medium Enhanced A0AV96 +ENSG00000163694 RBM47 seminal vesicle glandular cells Low Enhanced A0AV96 +ENSG00000163694 RBM47 testis Leydig cells Medium Enhanced A0AV96 +ENSG00000163714 U2SURP epididymis glandular cells High Enhanced O15042 +ENSG00000163714 U2SURP prostate glandular cells High Enhanced O15042 +ENSG00000163714 U2SURP seminal vesicle glandular cells High Enhanced O15042 +ENSG00000163714 U2SURP testis cells in seminiferous ducts High Enhanced O15042 +ENSG00000163714 U2SURP testis Leydig cells High Enhanced O15042 +ENSG00000163751 CPA3 prostate glandular cells Low Enhanced P15088 +ENSG00000163806 SPDYA testis elongated or late spermatids Medium Enhanced Q5MJ70 +ENSG00000163806 SPDYA testis Leydig cells Medium Enhanced Q5MJ70 +ENSG00000163806 SPDYA testis pachytene spermatocytes Medium Enhanced Q5MJ70 +ENSG00000163806 SPDYA testis preleptotene spermatocytes Low Enhanced Q5MJ70 +ENSG00000163806 SPDYA testis round or early spermatids Medium Enhanced Q5MJ70 +ENSG00000163806 SPDYA testis spermatogonia Low Enhanced Q5MJ70 +ENSG00000163810 TGM4 prostate glandular cells Medium Enhanced NA +ENSG00000163814 CDCP1 epididymis glandular cells Medium Enhanced Q9H5V8 +ENSG00000163814 CDCP1 prostate glandular cells Medium Enhanced Q9H5V8 +ENSG00000163814 CDCP1 seminal vesicle glandular cells Medium Enhanced Q9H5V8 +ENSG00000163814 CDCP1 testis cells in seminiferous ducts Low Enhanced Q9H5V8 +ENSG00000163814 CDCP1 testis Leydig cells Medium Enhanced Q9H5V8 +ENSG00000163818 LZTFL1 epididymis glandular cells Medium Enhanced Q9NQ48 +ENSG00000163818 LZTFL1 seminal vesicle glandular cells Low Enhanced Q9NQ48 +ENSG00000163818 LZTFL1 testis cells in seminiferous ducts High Enhanced Q9NQ48 +ENSG00000163848 ZNF148 epididymis glandular cells Medium Supported Q9UQR1 +ENSG00000163848 ZNF148 prostate glandular cells Medium Supported Q9UQR1 +ENSG00000163848 ZNF148 seminal vesicle glandular cells Medium Supported Q9UQR1 +ENSG00000163848 ZNF148 testis cells in seminiferous ducts Medium Supported Q9UQR1 +ENSG00000163848 ZNF148 testis Leydig cells Medium Supported Q9UQR1 +ENSG00000163877 SNIP1 epididymis glandular cells Low Enhanced Q8TAD8 +ENSG00000163877 SNIP1 testis cells in seminiferous ducts High Enhanced Q8TAD8 +ENSG00000163877 SNIP1 testis Leydig cells High Enhanced Q8TAD8 +ENSG00000163882 POLR2H epididymis glandular cells Medium Enhanced P52434 +ENSG00000163882 POLR2H prostate glandular cells Medium Enhanced P52434 +ENSG00000163882 POLR2H seminal vesicle glandular cells Medium Enhanced P52434 +ENSG00000163882 POLR2H testis cells in seminiferous ducts High Enhanced P52434 +ENSG00000163882 POLR2H testis Leydig cells Medium Enhanced P52434 +ENSG00000163885 CFAP100 testis preleptotene spermatocytes Low Enhanced Q494V2 +ENSG00000163885 CFAP100 testis spermatogonia Low Enhanced Q494V2 +ENSG00000163902 RPN1 epididymis glandular cells High Enhanced P04843 +ENSG00000163902 RPN1 prostate glandular cells Medium Enhanced P04843 +ENSG00000163902 RPN1 seminal vesicle glandular cells Medium Enhanced P04843 +ENSG00000163902 RPN1 testis cells in seminiferous ducts Medium Enhanced P04843 +ENSG00000163902 RPN1 testis Leydig cells High Enhanced P04843 +ENSG00000163918 RFC4 epididymis glandular cells Low Enhanced P35249 +ENSG00000163918 RFC4 prostate glandular cells Medium Enhanced P35249 +ENSG00000163918 RFC4 seminal vesicle glandular cells Low Enhanced P35249 +ENSG00000163918 RFC4 testis cells in seminiferous ducts High Enhanced P35249 +ENSG00000163918 RFC4 testis Leydig cells Low Enhanced P35249 +ENSG00000163931 TKT epididymis glandular cells Medium Enhanced P29401 +ENSG00000163931 TKT prostate glandular cells Medium Enhanced P29401 +ENSG00000163931 TKT seminal vesicle glandular cells Medium Enhanced P29401 +ENSG00000163931 TKT testis cells in seminiferous ducts Medium Enhanced P29401 +ENSG00000163931 TKT testis Leydig cells High Enhanced P29401 +ENSG00000163932 PRKCD epididymis glandular cells High Enhanced Q05655 +ENSG00000163932 PRKCD prostate glandular cells Medium Enhanced Q05655 +ENSG00000163932 PRKCD seminal vesicle glandular cells High Enhanced Q05655 +ENSG00000163932 PRKCD testis cells in seminiferous ducts Medium Enhanced Q05655 +ENSG00000163932 PRKCD testis Leydig cells Medium Enhanced Q05655 +ENSG00000163938 GNL3 epididymis glandular cells Medium Enhanced Q9BVP2 +ENSG00000163938 GNL3 prostate glandular cells Medium Enhanced Q9BVP2 +ENSG00000163938 GNL3 seminal vesicle glandular cells Medium Enhanced Q9BVP2 +ENSG00000163938 GNL3 testis cells in seminiferous ducts Medium Enhanced Q9BVP2 +ENSG00000163938 GNL3 testis Leydig cells Low Enhanced Q9BVP2 +ENSG00000163950 SLBP epididymis glandular cells Low Enhanced Q14493 +ENSG00000163950 SLBP seminal vesicle glandular cells Medium Enhanced Q14493 +ENSG00000163950 SLBP testis cells in seminiferous ducts High Enhanced Q14493 +ENSG00000163950 SLBP testis Leydig cells Medium Enhanced Q14493 +ENSG00000163956 LRPAP1 epididymis glandular cells High Enhanced P30533 +ENSG00000163956 LRPAP1 prostate glandular cells Medium Enhanced P30533 +ENSG00000163956 LRPAP1 seminal vesicle glandular cells Medium Enhanced P30533 +ENSG00000163956 LRPAP1 testis cells in seminiferous ducts High Enhanced P30533 +ENSG00000163956 LRPAP1 testis Leydig cells High Enhanced P30533 +ENSG00000163959 SLC51A epididymis glandular cells Low Enhanced Q86UW1 +ENSG00000163959 SLC51A prostate glandular cells Low Enhanced Q86UW1 +ENSG00000163959 SLC51A seminal vesicle glandular cells Low Enhanced Q86UW1 +ENSG00000163959 SLC51A testis Leydig cells Medium Enhanced Q86UW1 +ENSG00000163960 UBXN7 epididymis glandular cells High Enhanced O94888 +ENSG00000163960 UBXN7 prostate glandular cells Medium Enhanced O94888 +ENSG00000163960 UBXN7 seminal vesicle glandular cells Medium Enhanced O94888 +ENSG00000163960 UBXN7 testis cells in seminiferous ducts Medium Enhanced O94888 +ENSG00000163960 UBXN7 testis Leydig cells Medium Enhanced O94888 +ENSG00000163993 S100P prostate glandular cells Medium Enhanced P25815 +ENSG00000164022 AIMP1 epididymis glandular cells Medium Supported Q12904 +ENSG00000164022 AIMP1 prostate glandular cells Medium Supported Q12904 +ENSG00000164022 AIMP1 seminal vesicle glandular cells Medium Supported Q12904 +ENSG00000164022 AIMP1 testis cells in seminiferous ducts Medium Supported Q12904 +ENSG00000164022 AIMP1 testis Leydig cells Medium Supported Q12904 +ENSG00000164023 SGMS2 epididymis glandular cells Medium Enhanced Q8NHU3 +ENSG00000164023 SGMS2 prostate glandular cells Medium Enhanced Q8NHU3 +ENSG00000164023 SGMS2 seminal vesicle glandular cells High Enhanced Q8NHU3 +ENSG00000164023 SGMS2 testis cells in seminiferous ducts Medium Enhanced Q8NHU3 +ENSG00000164023 SGMS2 testis Leydig cells Medium Enhanced Q8NHU3 +ENSG00000164032 H2AFZ epididymis glandular cells High Supported P0C0S5 +ENSG00000164032 H2AFZ prostate glandular cells High Supported P0C0S5 +ENSG00000164032 H2AFZ seminal vesicle glandular cells High Supported P0C0S5 +ENSG00000164032 H2AFZ testis cells in seminiferous ducts High Supported P0C0S5 +ENSG00000164032 H2AFZ testis Leydig cells Medium Supported P0C0S5 +ENSG00000164039 BDH2 epididymis glandular cells Low Enhanced Q9BUT1 +ENSG00000164039 BDH2 prostate glandular cells Low Enhanced Q9BUT1 +ENSG00000164039 BDH2 seminal vesicle glandular cells Medium Enhanced Q9BUT1 +ENSG00000164039 BDH2 testis cells in seminiferous ducts Medium Enhanced Q9BUT1 +ENSG00000164039 BDH2 testis Leydig cells Medium Enhanced Q9BUT1 +ENSG00000164047 CAMP epididymis glandular cells Low Enhanced P49913 +ENSG00000164050 PLXNB1 epididymis glandular cells Medium Enhanced O43157 +ENSG00000164050 PLXNB1 prostate glandular cells Medium Enhanced O43157 +ENSG00000164050 PLXNB1 seminal vesicle glandular cells Medium Enhanced O43157 +ENSG00000164050 PLXNB1 testis cells in seminiferous ducts High Enhanced O43157 +ENSG00000164050 PLXNB1 testis Leydig cells Medium Enhanced O43157 +ENSG00000164051 CCDC51 epididymis glandular cells Medium Supported Q96ER9 +ENSG00000164051 CCDC51 prostate glandular cells Medium Supported Q96ER9 +ENSG00000164051 CCDC51 seminal vesicle glandular cells High Supported Q96ER9 +ENSG00000164051 CCDC51 testis cells in seminiferous ducts Medium Supported Q96ER9 +ENSG00000164051 CCDC51 testis Leydig cells High Supported Q96ER9 +ENSG00000164062 APEH epididymis glandular cells Medium Enhanced P13798 +ENSG00000164062 APEH prostate glandular cells Medium Enhanced P13798 +ENSG00000164062 APEH seminal vesicle glandular cells Medium Enhanced P13798 +ENSG00000164062 APEH testis cells in seminiferous ducts Medium Enhanced P13798 +ENSG00000164062 APEH testis Leydig cells Low Enhanced P13798 +ENSG00000164066 INTU epididymis glandular cells Medium Enhanced Q9ULD6 +ENSG00000164066 INTU prostate glandular cells Medium Enhanced Q9ULD6 +ENSG00000164066 INTU seminal vesicle glandular cells High Enhanced Q9ULD6 +ENSG00000164066 INTU testis cells in seminiferous ducts Medium Enhanced Q9ULD6 +ENSG00000164066 INTU testis Leydig cells Medium Enhanced Q9ULD6 +ENSG00000164070 HSPA4L testis elongated or late spermatids High Enhanced O95757 +ENSG00000164070 HSPA4L testis pachytene spermatocytes Medium Enhanced O95757 +ENSG00000164070 HSPA4L testis preleptotene spermatocytes Low Enhanced O95757 +ENSG00000164070 HSPA4L testis round or early spermatids High Enhanced O95757 +ENSG00000164070 HSPA4L testis spermatogonia Low Enhanced O95757 +ENSG00000164078 MST1R epididymis glandular cells Medium Enhanced Q04912 +ENSG00000164078 MST1R prostate glandular cells Medium Enhanced Q04912 +ENSG00000164078 MST1R seminal vesicle glandular cells Medium Enhanced Q04912 +ENSG00000164078 MST1R testis cells in seminiferous ducts Low Enhanced Q04912 +ENSG00000164078 MST1R testis Leydig cells Medium Enhanced Q04912 +ENSG00000164081 TEX264 seminal vesicle glandular cells Medium Enhanced Q9Y6I9 +ENSG00000164081 TEX264 testis cells in seminiferous ducts High Enhanced Q9Y6I9 +ENSG00000164081 TEX264 testis Leydig cells Low Enhanced Q9Y6I9 +ENSG00000164104 HMGB2 epididymis glandular cells Low Enhanced P26583 +ENSG00000164104 HMGB2 prostate glandular cells Low Enhanced P26583 +ENSG00000164104 HMGB2 seminal vesicle glandular cells Low Enhanced P26583 +ENSG00000164104 HMGB2 testis cells in seminiferous ducts High Enhanced P26583 +ENSG00000164104 HMGB2 testis Leydig cells Low Enhanced P26583 +ENSG00000164105 SAP30 epididymis glandular cells Medium Enhanced O75446 +ENSG00000164105 SAP30 prostate glandular cells Medium Enhanced O75446 +ENSG00000164105 SAP30 testis cells in seminiferous ducts Medium Enhanced O75446 +ENSG00000164105 SAP30 testis Leydig cells Medium Enhanced O75446 +ENSG00000164120 HPGD epididymis glandular cells Medium Enhanced P15428 +ENSG00000164142 FAM160A1 epididymis glandular cells Medium Enhanced Q05DH4 +ENSG00000164142 FAM160A1 prostate glandular cells Medium Enhanced Q05DH4 +ENSG00000164142 FAM160A1 seminal vesicle glandular cells Low Enhanced Q05DH4 +ENSG00000164142 FAM160A1 testis cells in seminiferous ducts Medium Enhanced Q05DH4 +ENSG00000164142 FAM160A1 testis Leydig cells Medium Enhanced Q05DH4 +ENSG00000164144 ARFIP1 epididymis glandular cells High Enhanced P53367 +ENSG00000164144 ARFIP1 prostate glandular cells High Enhanced P53367 +ENSG00000164144 ARFIP1 seminal vesicle glandular cells High Enhanced P53367 +ENSG00000164144 ARFIP1 testis cells in seminiferous ducts Medium Enhanced P53367 +ENSG00000164144 ARFIP1 testis Leydig cells Medium Enhanced P53367 +ENSG00000164171 ITGA2 epididymis glandular cells High Enhanced P17301 +ENSG00000164171 ITGA2 prostate glandular cells Low Enhanced P17301 +ENSG00000164171 ITGA2 seminal vesicle glandular cells High Enhanced P17301 +ENSG00000164171 ITGA2 testis cells in seminiferous ducts Low Enhanced P17301 +ENSG00000164171 ITGA2 testis Leydig cells High Enhanced P17301 +ENSG00000164182 NDUFAF2 prostate glandular cells Medium Supported Q8N183 +ENSG00000164182 NDUFAF2 seminal vesicle glandular cells High Supported Q8N183 +ENSG00000164182 NDUFAF2 testis cells in seminiferous ducts High Supported Q8N183 +ENSG00000164182 NDUFAF2 testis Leydig cells High Supported Q8N183 +ENSG00000164244 PRRC1 epididymis glandular cells High Supported Q96M27 +ENSG00000164244 PRRC1 prostate glandular cells High Supported Q96M27 +ENSG00000164244 PRRC1 seminal vesicle glandular cells High Supported Q96M27 +ENSG00000164244 PRRC1 testis cells in seminiferous ducts Medium Supported Q96M27 +ENSG00000164244 PRRC1 testis Leydig cells High Supported Q96M27 +ENSG00000164258 NDUFS4 epididymis glandular cells Medium Supported O43181 +ENSG00000164258 NDUFS4 prostate glandular cells High Supported O43181 +ENSG00000164258 NDUFS4 seminal vesicle glandular cells High Supported O43181 +ENSG00000164258 NDUFS4 testis cells in seminiferous ducts Medium Supported O43181 +ENSG00000164258 NDUFS4 testis Leydig cells Medium Supported O43181 +ENSG00000164294 GPX8 epididymis glandular cells Low Enhanced Q8TED1 +ENSG00000164294 GPX8 prostate glandular cells Low Enhanced Q8TED1 +ENSG00000164294 GPX8 seminal vesicle glandular cells Low Enhanced Q8TED1 +ENSG00000164294 GPX8 testis cells in seminiferous ducts Low Enhanced Q8TED1 +ENSG00000164300 SERINC5 epididymis glandular cells Medium Supported Q86VE9 +ENSG00000164300 SERINC5 prostate glandular cells High Supported Q86VE9 +ENSG00000164300 SERINC5 seminal vesicle glandular cells Medium Supported Q86VE9 +ENSG00000164300 SERINC5 testis cells in seminiferous ducts High Supported Q86VE9 +ENSG00000164300 SERINC5 testis Leydig cells Medium Supported Q86VE9 +ENSG00000164305 CASP3 seminal vesicle glandular cells Medium Enhanced P42574 +ENSG00000164305 CASP3 testis cells in seminiferous ducts Low Enhanced P42574 +ENSG00000164305 CASP3 testis Leydig cells Low Enhanced P42574 +ENSG00000164308 ERAP2 epididymis glandular cells Medium Enhanced Q6P179 +ENSG00000164308 ERAP2 prostate glandular cells Low Enhanced Q6P179 +ENSG00000164308 ERAP2 seminal vesicle glandular cells Low Enhanced Q6P179 +ENSG00000164308 ERAP2 testis cells in seminiferous ducts Low Enhanced Q6P179 +ENSG00000164308 ERAP2 testis Leydig cells Medium Enhanced Q6P179 +ENSG00000164334 FAM170A testis cells in seminiferous ducts Medium Enhanced A1A519 +ENSG00000164342 TLR3 epididymis glandular cells Medium Enhanced O15455 +ENSG00000164342 TLR3 prostate glandular cells Low Enhanced O15455 +ENSG00000164342 TLR3 seminal vesicle glandular cells Low Enhanced O15455 +ENSG00000164342 TLR3 testis cells in seminiferous ducts Low Enhanced O15455 +ENSG00000164342 TLR3 testis Leydig cells Medium Enhanced O15455 +ENSG00000164363 SLC6A18 epididymis glandular cells Medium Enhanced Q96N87 +ENSG00000164398 ACSL6 prostate glandular cells Low Enhanced Q9UKU0 +ENSG00000164398 ACSL6 seminal vesicle glandular cells High Enhanced Q9UKU0 +ENSG00000164398 ACSL6 testis elongated or late spermatids High Enhanced Q9UKU0 +ENSG00000164398 ACSL6 testis Leydig cells Medium Enhanced Q9UKU0 +ENSG00000164398 ACSL6 testis pachytene spermatocytes Low Enhanced Q9UKU0 +ENSG00000164398 ACSL6 testis round or early spermatids Low Enhanced Q9UKU0 +ENSG00000164404 GDF9 testis peritubular cells Medium Supported O60383 +ENSG00000164430 MB21D1 epididymis glandular cells Medium Enhanced Q8N884 +ENSG00000164430 MB21D1 prostate glandular cells Medium Enhanced Q8N884 +ENSG00000164430 MB21D1 seminal vesicle glandular cells Medium Enhanced Q8N884 +ENSG00000164430 MB21D1 testis cells in seminiferous ducts Medium Enhanced Q8N884 +ENSG00000164430 MB21D1 testis Leydig cells Medium Enhanced Q8N884 +ENSG00000164442 CITED2 epididymis glandular cells Medium Supported Q99967 +ENSG00000164442 CITED2 prostate glandular cells High Supported Q99967 +ENSG00000164442 CITED2 seminal vesicle glandular cells Medium Supported Q99967 +ENSG00000164442 CITED2 testis cells in seminiferous ducts High Supported Q99967 +ENSG00000164442 CITED2 testis Leydig cells High Supported Q99967 +ENSG00000164506 STXBP5 epididymis glandular cells Low Enhanced Q5T5C0 +ENSG00000164506 STXBP5 prostate glandular cells Low Enhanced Q5T5C0 +ENSG00000164506 STXBP5 seminal vesicle glandular cells Medium Enhanced Q5T5C0 +ENSG00000164506 STXBP5 testis Leydig cells Medium Enhanced Q5T5C0 +ENSG00000164508 HIST1H2AA epididymis glandular cells Medium Supported Q96QV6 +ENSG00000164508 HIST1H2AA prostate glandular cells Low Supported Q96QV6 +ENSG00000164508 HIST1H2AA seminal vesicle glandular cells Medium Supported Q96QV6 +ENSG00000164508 HIST1H2AA testis cells in seminiferous ducts High Supported Q96QV6 +ENSG00000164508 HIST1H2AA testis elongated or late spermatids High Supported Q96QV6 +ENSG00000164508 HIST1H2AA testis pachytene spermatocytes High Supported Q96QV6 +ENSG00000164508 HIST1H2AA testis preleptotene spermatocytes High Supported Q96QV6 +ENSG00000164508 HIST1H2AA testis round or early spermatids High Supported Q96QV6 +ENSG00000164508 HIST1H2AA testis spermatogonia High Supported Q96QV6 +ENSG00000164611 PTTG1 epididymis glandular cells Low Enhanced O95997 +ENSG00000164611 PTTG1 seminal vesicle glandular cells Medium Enhanced O95997 +ENSG00000164611 PTTG1 testis Leydig cells Low Enhanced O95997 +ENSG00000164611 PTTG1 testis pachytene spermatocytes High Enhanced O95997 +ENSG00000164611 PTTG1 testis preleptotene spermatocytes Low Enhanced O95997 +ENSG00000164627 KIF6 epididymis glandular cells Low Enhanced Q6ZMV9 +ENSG00000164627 KIF6 testis elongated or late spermatids Low Enhanced Q6ZMV9 +ENSG00000164627 KIF6 testis Leydig cells Low Enhanced Q6ZMV9 +ENSG00000164627 KIF6 testis pachytene spermatocytes Medium Enhanced Q6ZMV9 +ENSG00000164627 KIF6 testis round or early spermatids Medium Enhanced Q6ZMV9 +ENSG00000164695 CHMP4C epididymis glandular cells Medium Enhanced Q96CF2 +ENSG00000164695 CHMP4C prostate glandular cells Low Enhanced Q96CF2 +ENSG00000164695 CHMP4C seminal vesicle glandular cells Medium Enhanced Q96CF2 +ENSG00000164695 CHMP4C testis cells in seminiferous ducts Low Enhanced Q96CF2 +ENSG00000164695 CHMP4C testis Leydig cells Medium Enhanced Q96CF2 +ENSG00000164708 PGAM2 testis cells in seminiferous ducts Medium Enhanced P15259 +ENSG00000164708 PGAM2 testis Leydig cells Medium Enhanced P15259 +ENSG00000164736 SOX17 prostate glandular cells Low Enhanced Q9H6I2 +ENSG00000164736 SOX17 testis cells in seminiferous ducts Low Enhanced Q9H6I2 +ENSG00000164736 SOX17 testis Leydig cells Medium Enhanced Q9H6I2 +ENSG00000164754 RAD21 epididymis glandular cells High Supported O60216 +ENSG00000164754 RAD21 prostate glandular cells High Supported O60216 +ENSG00000164754 RAD21 seminal vesicle glandular cells High Supported O60216 +ENSG00000164754 RAD21 testis cells in seminiferous ducts High Supported O60216 +ENSG00000164754 RAD21 testis Leydig cells High Supported O60216 +ENSG00000164828 SUN1 epididymis glandular cells High Enhanced O94901 +ENSG00000164828 SUN1 prostate glandular cells Medium Enhanced O94901 +ENSG00000164828 SUN1 seminal vesicle glandular cells High Enhanced O94901 +ENSG00000164828 SUN1 testis cells in seminiferous ducts High Enhanced O94901 +ENSG00000164828 SUN1 testis Leydig cells High Enhanced O94901 +ENSG00000164830 OXR1 epididymis glandular cells Medium Enhanced Q8N573 +ENSG00000164830 OXR1 prostate glandular cells Medium Enhanced Q8N573 +ENSG00000164830 OXR1 seminal vesicle glandular cells Medium Enhanced Q8N573 +ENSG00000164830 OXR1 testis cells in seminiferous ducts Medium Enhanced Q8N573 +ENSG00000164830 OXR1 testis Leydig cells Low Enhanced Q8N573 +ENSG00000164871 SPAG11B epididymis glandular cells High Supported H0YF39 +ENSG00000164877 MICALL2 epididymis glandular cells Low Enhanced Q8IY33 +ENSG00000164877 MICALL2 seminal vesicle glandular cells Low Enhanced Q8IY33 +ENSG00000164877 MICALL2 testis cells in seminiferous ducts Low Enhanced Q8IY33 +ENSG00000164877 MICALL2 testis Leydig cells Low Enhanced Q8IY33 +ENSG00000164885 CDK5 epididymis glandular cells Medium Enhanced Q00535 +ENSG00000164885 CDK5 prostate glandular cells Low Enhanced Q00535 +ENSG00000164885 CDK5 seminal vesicle glandular cells Medium Enhanced Q00535 +ENSG00000164885 CDK5 testis cells in seminiferous ducts Medium Enhanced Q00535 +ENSG00000164885 CDK5 testis Leydig cells Medium Enhanced Q00535 +ENSG00000164889 SLC4A2 epididymis glandular cells Low Enhanced P04920 +ENSG00000164889 SLC4A2 prostate glandular cells Low Enhanced P04920 +ENSG00000164889 SLC4A2 seminal vesicle glandular cells Low Enhanced P04920 +ENSG00000164889 SLC4A2 testis cells in seminiferous ducts Medium Enhanced P04920 +ENSG00000164889 SLC4A2 testis Leydig cells Medium Enhanced P04920 +ENSG00000164902 PHAX epididymis glandular cells Medium Enhanced Q9H814 +ENSG00000164902 PHAX prostate glandular cells Medium Enhanced Q9H814 +ENSG00000164902 PHAX seminal vesicle glandular cells Medium Enhanced Q9H814 +ENSG00000164902 PHAX testis cells in seminiferous ducts Medium Enhanced Q9H814 +ENSG00000164902 PHAX testis Leydig cells Medium Enhanced Q9H814 +ENSG00000164904 ALDH7A1 epididymis glandular cells Low Enhanced P49419 +ENSG00000164904 ALDH7A1 prostate glandular cells Medium Enhanced P49419 +ENSG00000164904 ALDH7A1 seminal vesicle glandular cells Medium Enhanced P49419 +ENSG00000164904 ALDH7A1 testis cells in seminiferous ducts Medium Enhanced P49419 +ENSG00000164904 ALDH7A1 testis Leydig cells Medium Enhanced P49419 +ENSG00000164916 FOXK1 epididymis glandular cells High Enhanced P85037 +ENSG00000164916 FOXK1 prostate glandular cells High Enhanced P85037 +ENSG00000164916 FOXK1 seminal vesicle glandular cells High Enhanced P85037 +ENSG00000164916 FOXK1 testis cells in seminiferous ducts High Enhanced P85037 +ENSG00000164916 FOXK1 testis Leydig cells High Enhanced P85037 +ENSG00000164919 COX6C epididymis glandular cells Medium Enhanced P09669 +ENSG00000164919 COX6C prostate glandular cells High Enhanced P09669 +ENSG00000164919 COX6C seminal vesicle glandular cells High Enhanced P09669 +ENSG00000164919 COX6C testis cells in seminiferous ducts High Enhanced P09669 +ENSG00000164919 COX6C testis Leydig cells Medium Enhanced P09669 +ENSG00000164961 WASHC5 epididymis glandular cells Medium Enhanced Q12768 +ENSG00000164961 WASHC5 prostate glandular cells Low Enhanced Q12768 +ENSG00000164961 WASHC5 seminal vesicle glandular cells Medium Enhanced Q12768 +ENSG00000164961 WASHC5 testis cells in seminiferous ducts Medium Enhanced Q12768 +ENSG00000164961 WASHC5 testis Leydig cells Medium Enhanced Q12768 +ENSG00000164972 C9orf24 testis elongated or late spermatids High Enhanced Q8NCR6 +ENSG00000164985 PSIP1 epididymis glandular cells Medium Enhanced O75475 +ENSG00000164985 PSIP1 prostate glandular cells Medium Enhanced O75475 +ENSG00000164985 PSIP1 seminal vesicle glandular cells Medium Enhanced O75475 +ENSG00000164985 PSIP1 testis cells in seminiferous ducts High Enhanced O75475 +ENSG00000164985 PSIP1 testis Leydig cells Medium Enhanced O75475 +ENSG00000165025 SYK epididymis glandular cells Medium Enhanced P43405 +ENSG00000165025 SYK testis cells in seminiferous ducts Medium Enhanced P43405 +ENSG00000165059 PRKACG testis cells in seminiferous ducts High Supported P22612 +ENSG00000165059 PRKACG testis Leydig cells Medium Supported P22612 +ENSG00000165060 FXN epididymis glandular cells Medium Supported Q16595 +ENSG00000165060 FXN prostate glandular cells Medium Supported Q16595 +ENSG00000165060 FXN seminal vesicle glandular cells High Supported Q16595 +ENSG00000165060 FXN testis cells in seminiferous ducts Medium Supported Q16595 +ENSG00000165060 FXN testis Leydig cells Medium Supported Q16595 +ENSG00000165076 PRSS37 testis cells in seminiferous ducts High Enhanced A4D1T9 +ENSG00000165113 GKAP1 testis cells in seminiferous ducts Medium Enhanced Q5VSY0 +ENSG00000165119 HNRNPK epididymis glandular cells High Supported P61978 +ENSG00000165119 HNRNPK prostate glandular cells High Supported P61978 +ENSG00000165119 HNRNPK seminal vesicle glandular cells High Supported P61978 +ENSG00000165119 HNRNPK testis cells in seminiferous ducts High Supported P61978 +ENSG00000165119 HNRNPK testis Leydig cells High Supported P61978 +ENSG00000165140 FBP1 epididymis glandular cells Medium Enhanced P09467 +ENSG00000165140 FBP1 prostate glandular cells Medium Enhanced P09467 +ENSG00000165140 FBP1 seminal vesicle glandular cells Medium Enhanced P09467 +ENSG00000165140 FBP1 testis Leydig cells Low Enhanced P09467 +ENSG00000165185 KIAA1958 epididymis glandular cells Medium Enhanced Q8N8K9 +ENSG00000165185 KIAA1958 prostate glandular cells Medium Enhanced Q8N8K9 +ENSG00000165185 KIAA1958 seminal vesicle glandular cells Medium Enhanced Q8N8K9 +ENSG00000165185 KIAA1958 testis cells in seminiferous ducts Medium Enhanced Q8N8K9 +ENSG00000165185 KIAA1958 testis Leydig cells Medium Enhanced Q8N8K9 +ENSG00000165215 CLDN3 epididymis glandular cells Medium Supported O15551 +ENSG00000165215 CLDN3 prostate glandular cells High Supported O15551 +ENSG00000165215 CLDN3 seminal vesicle glandular cells High Supported O15551 +ENSG00000165238 WNK2 epididymis glandular cells Medium Enhanced Q9Y3S1 +ENSG00000165238 WNK2 prostate glandular cells High Enhanced Q9Y3S1 +ENSG00000165238 WNK2 seminal vesicle glandular cells Medium Enhanced Q9Y3S1 +ENSG00000165238 WNK2 testis cells in seminiferous ducts Medium Enhanced Q9Y3S1 +ENSG00000165238 WNK2 testis Leydig cells Low Enhanced Q9Y3S1 +ENSG00000165264 NDUFB6 epididymis glandular cells High Supported O95139 +ENSG00000165264 NDUFB6 prostate glandular cells High Supported O95139 +ENSG00000165264 NDUFB6 seminal vesicle glandular cells High Supported O95139 +ENSG00000165264 NDUFB6 testis cells in seminiferous ducts High Supported O95139 +ENSG00000165264 NDUFB6 testis Leydig cells High Supported O95139 +ENSG00000165271 NOL6 epididymis glandular cells Medium Supported Q9H6R4 +ENSG00000165271 NOL6 prostate glandular cells Medium Supported Q9H6R4 +ENSG00000165271 NOL6 seminal vesicle glandular cells Medium Supported Q9H6R4 +ENSG00000165271 NOL6 testis cells in seminiferous ducts Low Supported Q9H6R4 +ENSG00000165271 NOL6 testis Leydig cells Low Supported Q9H6R4 +ENSG00000165272 AQP3 epididymis glandular cells Low Enhanced Q92482 +ENSG00000165272 AQP3 prostate glandular cells High Enhanced Q92482 +ENSG00000165272 AQP3 seminal vesicle glandular cells Medium Enhanced Q92482 +ENSG00000165280 VCP epididymis glandular cells High Supported P55072 +ENSG00000165280 VCP prostate glandular cells High Supported P55072 +ENSG00000165280 VCP seminal vesicle glandular cells High Supported P55072 +ENSG00000165280 VCP testis cells in seminiferous ducts High Supported P55072 +ENSG00000165280 VCP testis Leydig cells High Supported P55072 +ENSG00000165283 STOML2 epididymis glandular cells High Supported Q9UJZ1 +ENSG00000165283 STOML2 prostate glandular cells High Supported Q9UJZ1 +ENSG00000165283 STOML2 seminal vesicle glandular cells High Supported Q9UJZ1 +ENSG00000165283 STOML2 testis cells in seminiferous ducts High Supported Q9UJZ1 +ENSG00000165283 STOML2 testis Leydig cells High Supported Q9UJZ1 +ENSG00000165309 ARMC3 testis elongated or late spermatids Medium Enhanced Q5W041 +ENSG00000165309 ARMC3 testis Leydig cells Medium Enhanced Q5W041 +ENSG00000165309 ARMC3 testis pachytene spermatocytes Low Enhanced Q5W041 +ENSG00000165309 ARMC3 testis round or early spermatids Medium Enhanced Q5W041 +ENSG00000165322 ARHGAP12 epididymis glandular cells High Enhanced Q8IWW6 +ENSG00000165322 ARHGAP12 prostate glandular cells Medium Enhanced Q8IWW6 +ENSG00000165322 ARHGAP12 seminal vesicle glandular cells Medium Enhanced Q8IWW6 +ENSG00000165322 ARHGAP12 testis cells in seminiferous ducts Medium Enhanced Q8IWW6 +ENSG00000165322 ARHGAP12 testis Leydig cells Medium Enhanced Q8IWW6 +ENSG00000165376 CLDN2 seminal vesicle glandular cells Low Enhanced P57739 +ENSG00000165383 LRRC18 testis elongated or late spermatids Medium Enhanced Q8N456 +ENSG00000165410 CFL2 epididymis glandular cells Low Enhanced Q9Y281 +ENSG00000165410 CFL2 prostate glandular cells Low Enhanced Q9Y281 +ENSG00000165410 CFL2 testis cells in seminiferous ducts Medium Enhanced Q9Y281 +ENSG00000165410 CFL2 testis Leydig cells Medium Enhanced Q9Y281 +ENSG00000165462 PHOX2A testis cells in seminiferous ducts Low Enhanced O14813 +ENSG00000165475 CRYL1 epididymis glandular cells High Enhanced Q9Y2S2 +ENSG00000165475 CRYL1 prostate glandular cells Medium Enhanced Q9Y2S2 +ENSG00000165475 CRYL1 seminal vesicle glandular cells High Enhanced Q9Y2S2 +ENSG00000165475 CRYL1 testis Leydig cells Medium Enhanced Q9Y2S2 +ENSG00000165495 PKNOX2 epididymis glandular cells High Supported Q96KN3 +ENSG00000165495 PKNOX2 prostate glandular cells High Supported Q96KN3 +ENSG00000165495 PKNOX2 seminal vesicle glandular cells High Supported Q96KN3 +ENSG00000165495 PKNOX2 testis cells in seminiferous ducts High Supported Q96KN3 +ENSG00000165495 PKNOX2 testis Leydig cells High Supported Q96KN3 +ENSG00000165506 DNAAF2 epididymis glandular cells Medium Enhanced Q9NVR5 +ENSG00000165506 DNAAF2 prostate glandular cells Medium Enhanced Q9NVR5 +ENSG00000165506 DNAAF2 seminal vesicle glandular cells Medium Enhanced Q9NVR5 +ENSG00000165506 DNAAF2 testis cells in seminiferous ducts Medium Enhanced Q9NVR5 +ENSG00000165506 DNAAF2 testis Leydig cells Medium Enhanced Q9NVR5 +ENSG00000165568 AKR1E2 epididymis glandular cells Low Enhanced Q96JD6 +ENSG00000165568 AKR1E2 testis elongated or late spermatids Medium Enhanced Q96JD6 +ENSG00000165568 AKR1E2 testis Leydig cells Low Enhanced Q96JD6 +ENSG00000165568 AKR1E2 testis pachytene spermatocytes Low Enhanced Q96JD6 +ENSG00000165568 AKR1E2 testis preleptotene spermatocytes High Enhanced Q96JD6 +ENSG00000165568 AKR1E2 testis round or early spermatids Low Enhanced Q96JD6 +ENSG00000165568 AKR1E2 testis spermatogonia Medium Enhanced Q96JD6 +ENSG00000165630 PRPF18 epididymis glandular cells High Supported Q99633 +ENSG00000165630 PRPF18 prostate glandular cells Medium Supported Q99633 +ENSG00000165630 PRPF18 seminal vesicle glandular cells High Supported Q99633 +ENSG00000165630 PRPF18 testis cells in seminiferous ducts High Supported Q99633 +ENSG00000165630 PRPF18 testis Leydig cells High Supported Q99633 +ENSG00000165637 VDAC2 epididymis glandular cells Medium Enhanced P45880 +ENSG00000165637 VDAC2 prostate glandular cells Medium Enhanced P45880 +ENSG00000165637 VDAC2 seminal vesicle glandular cells High Enhanced P45880 +ENSG00000165637 VDAC2 testis cells in seminiferous ducts Medium Enhanced P45880 +ENSG00000165637 VDAC2 testis Leydig cells High Enhanced P45880 +ENSG00000165671 NSD1 epididymis glandular cells Medium Supported Q96L73 +ENSG00000165671 NSD1 seminal vesicle glandular cells High Supported Q96L73 +ENSG00000165671 NSD1 testis cells in seminiferous ducts High Supported Q96L73 +ENSG00000165671 NSD1 testis Leydig cells High Supported Q96L73 +ENSG00000165672 PRDX3 epididymis glandular cells High Enhanced P30048 +ENSG00000165672 PRDX3 prostate glandular cells Medium Enhanced P30048 +ENSG00000165672 PRDX3 testis cells in seminiferous ducts Medium Enhanced P30048 +ENSG00000165672 PRDX3 testis Leydig cells High Enhanced P30048 +ENSG00000165685 TMEM52B prostate glandular cells Low Enhanced Q4KMG9 +ENSG00000165688 PMPCA epididymis glandular cells Medium Enhanced Q10713 +ENSG00000165688 PMPCA prostate glandular cells Medium Enhanced Q10713 +ENSG00000165688 PMPCA seminal vesicle glandular cells High Enhanced Q10713 +ENSG00000165688 PMPCA testis cells in seminiferous ducts High Enhanced Q10713 +ENSG00000165688 PMPCA testis Leydig cells High Enhanced Q10713 +ENSG00000165695 AK8 epididymis glandular cells Low Enhanced Q96MA6 +ENSG00000165695 AK8 prostate glandular cells Low Enhanced Q96MA6 +ENSG00000165695 AK8 testis cells in seminiferous ducts Medium Enhanced Q96MA6 +ENSG00000165695 AK8 testis Leydig cells Medium Enhanced Q96MA6 +ENSG00000165698 SPACA9 testis elongated or late spermatids High Enhanced Q96E40 +ENSG00000165699 TSC1 epididymis glandular cells Medium Supported Q92574 +ENSG00000165699 TSC1 prostate glandular cells Medium Supported Q92574 +ENSG00000165699 TSC1 seminal vesicle glandular cells Medium Supported Q92574 +ENSG00000165699 TSC1 testis cells in seminiferous ducts Medium Supported Q92574 +ENSG00000165699 TSC1 testis Leydig cells Medium Supported Q92574 +ENSG00000165704 HPRT1 epididymis glandular cells High Enhanced P00492 +ENSG00000165704 HPRT1 prostate glandular cells Medium Enhanced P00492 +ENSG00000165704 HPRT1 seminal vesicle glandular cells Medium Enhanced P00492 +ENSG00000165704 HPRT1 testis cells in seminiferous ducts High Enhanced P00492 +ENSG00000165704 HPRT1 testis Leydig cells Medium Enhanced P00492 +ENSG00000165724 ZMYND19 epididymis glandular cells Low Supported Q96E35 +ENSG00000165724 ZMYND19 prostate glandular cells Medium Supported Q96E35 +ENSG00000165724 ZMYND19 seminal vesicle glandular cells Medium Supported Q96E35 +ENSG00000165724 ZMYND19 testis cells in seminiferous ducts Low Supported Q96E35 +ENSG00000165724 ZMYND19 testis Leydig cells Medium Supported Q96E35 +ENSG00000165732 DDX21 epididymis glandular cells High Enhanced Q9NR30 +ENSG00000165732 DDX21 prostate glandular cells Low Enhanced Q9NR30 +ENSG00000165732 DDX21 seminal vesicle glandular cells High Enhanced Q9NR30 +ENSG00000165732 DDX21 testis cells in seminiferous ducts High Enhanced Q9NR30 +ENSG00000165732 DDX21 testis Leydig cells Medium Enhanced Q9NR30 +ENSG00000165757 KIAA1462 epididymis glandular cells Low Enhanced Q9P266 +ENSG00000165757 KIAA1462 prostate glandular cells Medium Enhanced Q9P266 +ENSG00000165757 KIAA1462 seminal vesicle glandular cells Low Enhanced Q9P266 +ENSG00000165757 KIAA1462 testis cells in seminiferous ducts Medium Enhanced Q9P266 +ENSG00000165757 KIAA1462 testis Leydig cells Medium Enhanced Q9P266 +ENSG00000165795 NDRG2 epididymis glandular cells High Enhanced Q9UN36 +ENSG00000165795 NDRG2 prostate glandular cells High Enhanced Q9UN36 +ENSG00000165795 NDRG2 seminal vesicle glandular cells High Enhanced Q9UN36 +ENSG00000165795 NDRG2 testis cells in seminiferous ducts Medium Enhanced Q9UN36 +ENSG00000165795 NDRG2 testis Leydig cells Medium Enhanced Q9UN36 +ENSG00000165802 NSMF epididymis glandular cells Medium Enhanced Q6X4W1 +ENSG00000165802 NSMF prostate glandular cells Low Enhanced Q6X4W1 +ENSG00000165802 NSMF seminal vesicle glandular cells Medium Enhanced Q6X4W1 +ENSG00000165802 NSMF testis cells in seminiferous ducts Medium Enhanced Q6X4W1 +ENSG00000165802 NSMF testis Leydig cells Medium Enhanced Q6X4W1 +ENSG00000165807 PPP1R36 testis cells in seminiferous ducts Medium Enhanced Q96LQ0 +ENSG00000165895 ARHGAP42 epididymis glandular cells Medium Enhanced A6NI28 +ENSG00000165895 ARHGAP42 prostate glandular cells Medium Enhanced A6NI28 +ENSG00000165895 ARHGAP42 seminal vesicle glandular cells Low Enhanced A6NI28 +ENSG00000165895 ARHGAP42 testis cells in seminiferous ducts High Enhanced A6NI28 +ENSG00000165895 ARHGAP42 testis Leydig cells Medium Enhanced A6NI28 +ENSG00000165914 TTC7B epididymis glandular cells Low Enhanced Q86TV6 +ENSG00000165914 TTC7B prostate glandular cells Medium Enhanced Q86TV6 +ENSG00000165934 CPSF2 epididymis glandular cells High Supported Q9P2I0 +ENSG00000165934 CPSF2 prostate glandular cells High Supported Q9P2I0 +ENSG00000165934 CPSF2 seminal vesicle glandular cells High Supported Q9P2I0 +ENSG00000165934 CPSF2 testis cells in seminiferous ducts High Supported Q9P2I0 +ENSG00000165934 CPSF2 testis Leydig cells High Supported Q9P2I0 +ENSG00000165959 CLMN epididymis glandular cells High Enhanced Q96JQ2 +ENSG00000165959 CLMN prostate glandular cells Medium Enhanced Q96JQ2 +ENSG00000165959 CLMN seminal vesicle glandular cells Medium Enhanced Q96JQ2 +ENSG00000165959 CLMN testis elongated or late spermatids High Enhanced Q96JQ2 +ENSG00000165959 CLMN testis Leydig cells Low Enhanced Q96JQ2 +ENSG00000165959 CLMN testis pachytene spermatocytes Low Enhanced Q96JQ2 +ENSG00000165959 CLMN testis round or early spermatids Medium Enhanced Q96JQ2 +ENSG00000165959 CLMN testis spermatogonia Low Enhanced Q96JQ2 +ENSG00000166033 HTRA1 epididymis glandular cells Low Enhanced Q92743 +ENSG00000166049 PASD1 testis preleptotene spermatocytes Medium Enhanced Q8IV76 +ENSG00000166049 PASD1 testis spermatogonia High Enhanced Q8IV76 +ENSG00000166069 TMCO5A testis elongated or late spermatids High Enhanced Q8N6Q1 +ENSG00000166069 TMCO5A testis Leydig cells Low Enhanced Q8N6Q1 +ENSG00000166069 TMCO5A testis round or early spermatids High Enhanced Q8N6Q1 +ENSG00000166118 SPATA19 testis elongated or late spermatids High Enhanced Q7Z5L4 +ENSG00000166118 SPATA19 testis Leydig cells Low Enhanced Q7Z5L4 +ENSG00000166118 SPATA19 testis pachytene spermatocytes Medium Enhanced Q7Z5L4 +ENSG00000166118 SPATA19 testis preleptotene spermatocytes Low Enhanced Q7Z5L4 +ENSG00000166118 SPATA19 testis round or early spermatids Medium Enhanced Q7Z5L4 +ENSG00000166118 SPATA19 testis spermatogonia Low Enhanced Q7Z5L4 +ENSG00000166130 IKBIP epididymis glandular cells Low Enhanced Q70UQ0 +ENSG00000166130 IKBIP testis cells in seminiferous ducts Low Enhanced Q70UQ0 +ENSG00000166130 IKBIP testis Leydig cells Low Enhanced Q70UQ0 +ENSG00000166135 HIF1AN epididymis glandular cells Medium Enhanced Q9NWT6 +ENSG00000166135 HIF1AN prostate glandular cells Medium Enhanced Q9NWT6 +ENSG00000166135 HIF1AN seminal vesicle glandular cells Medium Enhanced Q9NWT6 +ENSG00000166135 HIF1AN testis cells in seminiferous ducts Medium Enhanced Q9NWT6 +ENSG00000166135 HIF1AN testis Leydig cells Medium Enhanced Q9NWT6 +ENSG00000166136 NDUFB8 epididymis glandular cells Low Supported O95169 +ENSG00000166136 NDUFB8 prostate glandular cells Medium Supported O95169 +ENSG00000166136 NDUFB8 seminal vesicle glandular cells High Supported O95169 +ENSG00000166136 NDUFB8 testis cells in seminiferous ducts Low Supported O95169 +ENSG00000166136 NDUFB8 testis Leydig cells Medium Supported O95169 +ENSG00000166164 BRD7 epididymis glandular cells High Enhanced Q9NPI1 +ENSG00000166164 BRD7 prostate glandular cells High Enhanced Q9NPI1 +ENSG00000166164 BRD7 seminal vesicle glandular cells High Enhanced Q9NPI1 +ENSG00000166164 BRD7 testis cells in seminiferous ducts High Enhanced Q9NPI1 +ENSG00000166164 BRD7 testis Leydig cells Medium Enhanced Q9NPI1 +ENSG00000166165 CKB prostate glandular cells Medium Enhanced P12277 +ENSG00000166170 BAG5 testis cells in seminiferous ducts Medium Enhanced Q9UL15 +ENSG00000166171 DPCD testis cells in seminiferous ducts High Enhanced Q9BVM2 +ENSG00000166197 NOLC1 epididymis glandular cells Medium Supported Q14978 +ENSG00000166197 NOLC1 testis cells in seminiferous ducts Low Supported Q14978 +ENSG00000166197 NOLC1 testis Leydig cells Medium Supported Q14978 +ENSG00000166224 SGPL1 epididymis glandular cells Medium Enhanced O95470 +ENSG00000166224 SGPL1 prostate glandular cells Medium Enhanced O95470 +ENSG00000166224 SGPL1 seminal vesicle glandular cells Medium Enhanced O95470 +ENSG00000166224 SGPL1 testis cells in seminiferous ducts Medium Enhanced O95470 +ENSG00000166224 SGPL1 testis Leydig cells Low Enhanced O95470 +ENSG00000166226 CCT2 epididymis glandular cells Medium Enhanced P78371 +ENSG00000166226 CCT2 prostate glandular cells Low Enhanced P78371 +ENSG00000166226 CCT2 testis cells in seminiferous ducts High Enhanced P78371 +ENSG00000166226 CCT2 testis Leydig cells Low Enhanced P78371 +ENSG00000166246 C16orf71 testis elongated or late spermatids High Enhanced Q8IYS4 +ENSG00000166246 C16orf71 testis pachytene spermatocytes High Enhanced Q8IYS4 +ENSG00000166246 C16orf71 testis round or early spermatids High Enhanced Q8IYS4 +ENSG00000166333 ILK epididymis glandular cells Medium Enhanced Q13418 +ENSG00000166333 ILK prostate glandular cells Low Enhanced Q13418 +ENSG00000166333 ILK seminal vesicle glandular cells Medium Enhanced Q13418 +ENSG00000166333 ILK testis Leydig cells Medium Enhanced Q13418 +ENSG00000166337 TAF10 epididymis glandular cells High Supported Q12962 +ENSG00000166337 TAF10 prostate glandular cells High Supported Q12962 +ENSG00000166337 TAF10 seminal vesicle glandular cells High Supported Q12962 +ENSG00000166337 TAF10 testis cells in seminiferous ducts High Supported Q12962 +ENSG00000166337 TAF10 testis Leydig cells High Supported Q12962 +ENSG00000166340 TPP1 epididymis glandular cells High Enhanced O14773 +ENSG00000166340 TPP1 prostate glandular cells Medium Enhanced O14773 +ENSG00000166340 TPP1 seminal vesicle glandular cells High Enhanced O14773 +ENSG00000166340 TPP1 testis cells in seminiferous ducts Medium Enhanced O14773 +ENSG00000166340 TPP1 testis Leydig cells High Enhanced O14773 +ENSG00000166347 CYB5A seminal vesicle glandular cells Medium Enhanced P00167 +ENSG00000166347 CYB5A testis Leydig cells High Enhanced P00167 +ENSG00000166394 CYB5R2 testis cells in seminiferous ducts High Enhanced Q6BCY4 +ENSG00000166401 SERPINB8 prostate glandular cells Low Enhanced P50452 +ENSG00000166401 SERPINB8 testis cells in seminiferous ducts Low Enhanced P50452 +ENSG00000166411 IDH3A epididymis glandular cells High Supported P50213 +ENSG00000166411 IDH3A prostate glandular cells Medium Supported P50213 +ENSG00000166411 IDH3A seminal vesicle glandular cells Medium Supported P50213 +ENSG00000166411 IDH3A testis cells in seminiferous ducts Medium Supported P50213 +ENSG00000166411 IDH3A testis Leydig cells High Supported P50213 +ENSG00000166432 ZMAT1 testis cells in seminiferous ducts Medium Enhanced Q5H9K5 +ENSG00000166432 ZMAT1 testis Leydig cells Low Enhanced Q5H9K5 +ENSG00000166441 RPL27A epididymis glandular cells Medium Supported P46776 +ENSG00000166441 RPL27A prostate glandular cells Low Supported P46776 +ENSG00000166441 RPL27A seminal vesicle glandular cells Medium Supported P46776 +ENSG00000166441 RPL27A testis cells in seminiferous ducts Low Supported P46776 +ENSG00000166441 RPL27A testis Leydig cells Medium Supported P46776 +ENSG00000166477 LEO1 epididymis glandular cells Medium Enhanced Q8WVC0 +ENSG00000166477 LEO1 prostate glandular cells Medium Enhanced Q8WVC0 +ENSG00000166477 LEO1 seminal vesicle glandular cells Medium Enhanced Q8WVC0 +ENSG00000166477 LEO1 testis cells in seminiferous ducts High Enhanced Q8WVC0 +ENSG00000166477 LEO1 testis Leydig cells Medium Enhanced Q8WVC0 +ENSG00000166478 ZNF143 epididymis glandular cells Low Supported P52747 +ENSG00000166478 ZNF143 prostate glandular cells Low Supported P52747 +ENSG00000166478 ZNF143 seminal vesicle glandular cells Low Supported P52747 +ENSG00000166478 ZNF143 testis cells in seminiferous ducts Medium Supported P52747 +ENSG00000166478 ZNF143 testis Leydig cells Low Supported P52747 +ENSG00000166508 MCM7 epididymis glandular cells Medium Enhanced P33993 +ENSG00000166508 MCM7 prostate glandular cells Medium Enhanced P33993 +ENSG00000166508 MCM7 testis cells in seminiferous ducts High Enhanced P33993 +ENSG00000166508 MCM7 testis Leydig cells Low Enhanced P33993 +ENSG00000166510 CCDC68 epididymis glandular cells Medium Supported Q9H2F9 +ENSG00000166510 CCDC68 prostate glandular cells Medium Supported Q9H2F9 +ENSG00000166510 CCDC68 seminal vesicle glandular cells Medium Supported Q9H2F9 +ENSG00000166510 CCDC68 testis cells in seminiferous ducts High Supported Q9H2F9 +ENSG00000166510 CCDC68 testis Leydig cells High Supported Q9H2F9 +ENSG00000166526 ZNF3 epididymis glandular cells High Supported P17036 +ENSG00000166526 ZNF3 prostate glandular cells High Supported P17036 +ENSG00000166526 ZNF3 testis cells in seminiferous ducts High Supported P17036 +ENSG00000166526 ZNF3 testis Leydig cells Medium Supported P17036 +ENSG00000166578 IQCD testis round or early spermatids High Supported Q96DY2 +ENSG00000166582 CENPV epididymis glandular cells Low Enhanced Q7Z7K6 +ENSG00000166582 CENPV prostate glandular cells Low Enhanced Q7Z7K6 +ENSG00000166582 CENPV testis cells in seminiferous ducts Medium Enhanced Q7Z7K6 +ENSG00000166582 CENPV testis Leydig cells Low Enhanced Q7Z7K6 +ENSG00000166595 FAM96B epididymis glandular cells Medium Enhanced Q9Y3D0 +ENSG00000166595 FAM96B prostate glandular cells Medium Enhanced Q9Y3D0 +ENSG00000166595 FAM96B seminal vesicle glandular cells Medium Enhanced Q9Y3D0 +ENSG00000166595 FAM96B testis cells in seminiferous ducts Medium Enhanced Q9Y3D0 +ENSG00000166595 FAM96B testis Leydig cells Medium Enhanced Q9Y3D0 +ENSG00000166596 CFAP52 testis elongated or late spermatids Medium Enhanced Q8N1V2 +ENSG00000166596 CFAP52 testis Leydig cells Low Enhanced Q8N1V2 +ENSG00000166596 CFAP52 testis pachytene spermatocytes Medium Enhanced Q8N1V2 +ENSG00000166596 CFAP52 testis round or early spermatids Medium Enhanced Q8N1V2 +ENSG00000166598 HSP90B1 epididymis glandular cells High Enhanced P14625 +ENSG00000166598 HSP90B1 prostate glandular cells High Enhanced P14625 +ENSG00000166598 HSP90B1 seminal vesicle glandular cells High Enhanced P14625 +ENSG00000166598 HSP90B1 testis cells in seminiferous ducts High Enhanced P14625 +ENSG00000166598 HSP90B1 testis Leydig cells Medium Enhanced P14625 +ENSG00000166669 ATF7IP2 epididymis glandular cells Low Enhanced Q5U623 +ENSG00000166669 ATF7IP2 seminal vesicle glandular cells Low Enhanced Q5U623 +ENSG00000166669 ATF7IP2 testis elongated or late spermatids Medium Enhanced Q5U623 +ENSG00000166669 ATF7IP2 testis Leydig cells Low Enhanced Q5U623 +ENSG00000166669 ATF7IP2 testis pachytene spermatocytes High Enhanced Q5U623 +ENSG00000166669 ATF7IP2 testis peritubular cells Low Enhanced Q5U623 +ENSG00000166669 ATF7IP2 testis preleptotene spermatocytes Medium Enhanced Q5U623 +ENSG00000166669 ATF7IP2 testis round or early spermatids High Enhanced Q5U623 +ENSG00000166669 ATF7IP2 testis sertoli cells Medium Enhanced Q5U623 +ENSG00000166669 ATF7IP2 testis spermatogonia Medium Enhanced Q5U623 +ENSG00000166685 COG1 epididymis glandular cells Medium Supported Q8WTW3 +ENSG00000166685 COG1 prostate glandular cells High Supported Q8WTW3 +ENSG00000166685 COG1 seminal vesicle glandular cells High Supported Q8WTW3 +ENSG00000166685 COG1 testis cells in seminiferous ducts Medium Supported Q8WTW3 +ENSG00000166685 COG1 testis Leydig cells Medium Supported Q8WTW3 +ENSG00000166710 B2M epididymis glandular cells Medium Enhanced NA +ENSG00000166710 B2M prostate glandular cells Medium Enhanced NA +ENSG00000166710 B2M seminal vesicle glandular cells Medium Enhanced NA +ENSG00000166710 B2M testis cells in seminiferous ducts Low Enhanced NA +ENSG00000166710 B2M testis Leydig cells Medium Enhanced NA +ENSG00000166734 CASC4 epididymis glandular cells High Enhanced Q6P4E1 +ENSG00000166734 CASC4 prostate glandular cells High Enhanced Q6P4E1 +ENSG00000166734 CASC4 seminal vesicle glandular cells High Enhanced Q6P4E1 +ENSG00000166734 CASC4 testis cells in seminiferous ducts High Enhanced Q6P4E1 +ENSG00000166734 CASC4 testis Leydig cells High Enhanced Q6P4E1 +ENSG00000166794 PPIB epididymis glandular cells High Enhanced P23284 +ENSG00000166794 PPIB prostate glandular cells Medium Enhanced P23284 +ENSG00000166794 PPIB seminal vesicle glandular cells High Enhanced P23284 +ENSG00000166794 PPIB testis cells in seminiferous ducts Medium Enhanced P23284 +ENSG00000166794 PPIB testis Leydig cells Medium Enhanced P23284 +ENSG00000166796 LDHC testis elongated or late spermatids High Enhanced P07864 +ENSG00000166796 LDHC testis Leydig cells Low Enhanced P07864 +ENSG00000166796 LDHC testis pachytene spermatocytes Medium Enhanced P07864 +ENSG00000166796 LDHC testis preleptotene spermatocytes Medium Enhanced P07864 +ENSG00000166796 LDHC testis round or early spermatids High Enhanced P07864 +ENSG00000166796 LDHC testis spermatogonia Low Enhanced P07864 +ENSG00000166816 LDHD epididymis glandular cells Medium Enhanced Q86WU2 +ENSG00000166816 LDHD prostate glandular cells Medium Enhanced Q86WU2 +ENSG00000166816 LDHD seminal vesicle glandular cells Medium Enhanced Q86WU2 +ENSG00000166816 LDHD testis cells in seminiferous ducts Medium Enhanced Q86WU2 +ENSG00000166816 LDHD testis Leydig cells Medium Enhanced Q86WU2 +ENSG00000166825 ANPEP prostate glandular cells Medium Enhanced P15144 +ENSG00000166825 ANPEP testis Leydig cells Low Enhanced P15144 +ENSG00000166840 GLYATL1 prostate glandular cells Low Supported Q969I3 +ENSG00000166848 TERF2IP epididymis glandular cells Medium Supported Q9NYB0 +ENSG00000166848 TERF2IP prostate glandular cells Medium Supported Q9NYB0 +ENSG00000166848 TERF2IP seminal vesicle glandular cells Low Supported Q9NYB0 +ENSG00000166848 TERF2IP testis cells in seminiferous ducts Medium Supported Q9NYB0 +ENSG00000166848 TERF2IP testis Leydig cells Medium Supported Q9NYB0 +ENSG00000166856 GPR182 testis preleptotene spermatocytes Medium Enhanced O15218 +ENSG00000166856 GPR182 testis sertoli cells Medium Enhanced O15218 +ENSG00000166856 GPR182 testis spermatogonia Low Enhanced O15218 +ENSG00000166902 MRPL16 epididymis glandular cells High Supported Q9NX20 +ENSG00000166902 MRPL16 prostate glandular cells High Supported Q9NX20 +ENSG00000166902 MRPL16 seminal vesicle glandular cells High Supported Q9NX20 +ENSG00000166902 MRPL16 testis cells in seminiferous ducts High Supported Q9NX20 +ENSG00000166902 MRPL16 testis Leydig cells High Supported Q9NX20 +ENSG00000166913 YWHAB epididymis glandular cells High Enhanced P31946 +ENSG00000166913 YWHAB prostate glandular cells High Enhanced P31946 +ENSG00000166913 YWHAB seminal vesicle glandular cells High Enhanced P31946 +ENSG00000166913 YWHAB testis cells in seminiferous ducts High Enhanced P31946 +ENSG00000166913 YWHAB testis Leydig cells Medium Enhanced P31946 +ENSG00000166920 C15orf48 prostate glandular cells Low Enhanced Q9C002 +ENSG00000166920 C15orf48 testis cells in seminiferous ducts Medium Enhanced Q9C002 +ENSG00000166946 CCNDBP1 epididymis glandular cells High Supported O95273 +ENSG00000166946 CCNDBP1 prostate glandular cells High Supported O95273 +ENSG00000166946 CCNDBP1 seminal vesicle glandular cells High Supported O95273 +ENSG00000166946 CCNDBP1 testis cells in seminiferous ducts High Supported O95273 +ENSG00000166946 CCNDBP1 testis Leydig cells High Supported O95273 +ENSG00000166959 MS4A8 epididymis glandular cells Low Enhanced Q9BY19 +ENSG00000166959 MS4A8 seminal vesicle glandular cells Low Enhanced Q9BY19 +ENSG00000166959 MS4A8 testis Leydig cells Low Enhanced Q9BY19 +ENSG00000166965 RCCD1 epididymis glandular cells Medium Enhanced A6NED2 +ENSG00000166965 RCCD1 prostate glandular cells High Enhanced A6NED2 +ENSG00000166965 RCCD1 seminal vesicle glandular cells Medium Enhanced A6NED2 +ENSG00000166965 RCCD1 testis cells in seminiferous ducts High Enhanced A6NED2 +ENSG00000166965 RCCD1 testis Leydig cells High Enhanced A6NED2 +ENSG00000166974 MAPRE2 prostate glandular cells Low Enhanced Q15555 +ENSG00000166974 MAPRE2 testis Leydig cells Low Enhanced Q15555 +ENSG00000166979 EVA1C epididymis glandular cells Medium Enhanced P58658 +ENSG00000166979 EVA1C prostate glandular cells Medium Enhanced P58658 +ENSG00000166979 EVA1C seminal vesicle glandular cells Medium Enhanced P58658 +ENSG00000166979 EVA1C testis cells in seminiferous ducts Medium Enhanced P58658 +ENSG00000166979 EVA1C testis Leydig cells High Enhanced P58658 +ENSG00000166986 MARS epididymis glandular cells High Supported P56192 +ENSG00000166986 MARS prostate glandular cells Medium Supported P56192 +ENSG00000166986 MARS seminal vesicle glandular cells High Supported P56192 +ENSG00000166986 MARS testis cells in seminiferous ducts High Supported P56192 +ENSG00000166986 MARS testis Leydig cells Medium Supported P56192 +ENSG00000167004 PDIA3 epididymis glandular cells High Enhanced P30101 +ENSG00000167004 PDIA3 prostate glandular cells High Enhanced P30101 +ENSG00000167004 PDIA3 seminal vesicle glandular cells High Enhanced P30101 +ENSG00000167004 PDIA3 testis cells in seminiferous ducts High Enhanced P30101 +ENSG00000167004 PDIA3 testis Leydig cells High Enhanced P30101 +ENSG00000167034 NKX3-1 prostate glandular cells High Enhanced Q99801 +ENSG00000167034 NKX3-1 testis cells in seminiferous ducts Medium Enhanced Q99801 +ENSG00000167034 NKX3-1 testis Leydig cells Low Enhanced Q99801 +ENSG00000167081 PBX3 epididymis glandular cells Low Supported P40426 +ENSG00000167081 PBX3 prostate glandular cells Low Supported P40426 +ENSG00000167085 PHB epididymis glandular cells High Supported P35232 +ENSG00000167085 PHB prostate glandular cells High Supported P35232 +ENSG00000167085 PHB seminal vesicle glandular cells High Supported P35232 +ENSG00000167085 PHB testis cells in seminiferous ducts High Supported P35232 +ENSG00000167085 PHB testis Leydig cells High Supported P35232 +ENSG00000167088 SNRPD1 epididymis glandular cells Medium Supported P62314 +ENSG00000167088 SNRPD1 prostate glandular cells Medium Supported P62314 +ENSG00000167088 SNRPD1 seminal vesicle glandular cells Medium Supported P62314 +ENSG00000167088 SNRPD1 testis cells in seminiferous ducts Medium Supported P62314 +ENSG00000167088 SNRPD1 testis Leydig cells High Supported P62314 +ENSG00000167098 SUN5 testis Leydig cells Low Enhanced Q8TC36 +ENSG00000167098 SUN5 testis round or early spermatids High Enhanced Q8TC36 +ENSG00000167107 ACSF2 epididymis glandular cells Medium Enhanced Q96CM8 +ENSG00000167107 ACSF2 prostate glandular cells Low Enhanced Q96CM8 +ENSG00000167107 ACSF2 seminal vesicle glandular cells High Enhanced Q96CM8 +ENSG00000167107 ACSF2 testis cells in seminiferous ducts Low Enhanced Q96CM8 +ENSG00000167107 ACSF2 testis Leydig cells High Enhanced Q96CM8 +ENSG00000167110 GOLGA2 epididymis glandular cells Medium Enhanced Q08379 +ENSG00000167110 GOLGA2 prostate glandular cells Medium Enhanced Q08379 +ENSG00000167110 GOLGA2 seminal vesicle glandular cells Medium Enhanced Q08379 +ENSG00000167110 GOLGA2 testis cells in seminiferous ducts Medium Enhanced Q08379 +ENSG00000167110 GOLGA2 testis Leydig cells Medium Enhanced Q08379 +ENSG00000167113 COQ4 epididymis glandular cells High Supported Q9Y3A0 +ENSG00000167113 COQ4 prostate glandular cells High Supported Q9Y3A0 +ENSG00000167113 COQ4 seminal vesicle glandular cells High Supported Q9Y3A0 +ENSG00000167113 COQ4 testis cells in seminiferous ducts High Supported Q9Y3A0 +ENSG00000167113 COQ4 testis Leydig cells High Supported Q9Y3A0 +ENSG00000167139 TBC1D21 testis cells in seminiferous ducts High Enhanced Q8IYX1 +ENSG00000167139 TBC1D21 testis Leydig cells Low Enhanced Q8IYX1 +ENSG00000167182 SP2 epididymis glandular cells Medium Supported Q02086 +ENSG00000167182 SP2 prostate glandular cells Medium Supported Q02086 +ENSG00000167182 SP2 seminal vesicle glandular cells Low Supported Q02086 +ENSG00000167182 SP2 testis cells in seminiferous ducts Medium Supported Q02086 +ENSG00000167182 SP2 testis Leydig cells Low Supported Q02086 +ENSG00000167191 GPRC5B epididymis glandular cells Medium Enhanced Q9NZH0 +ENSG00000167191 GPRC5B prostate glandular cells Low Enhanced Q9NZH0 +ENSG00000167191 GPRC5B seminal vesicle glandular cells High Enhanced Q9NZH0 +ENSG00000167191 GPRC5B testis cells in seminiferous ducts Medium Enhanced Q9NZH0 +ENSG00000167191 GPRC5B testis Leydig cells Medium Enhanced Q9NZH0 +ENSG00000167195 GOLGA6C testis elongated or late spermatids High Supported A6NDK9 +ENSG00000167195 GOLGA6C testis round or early spermatids High Supported A6NDK9 +ENSG00000167195 GOLGA6C testis spermatogonia High Supported A6NDK9 +ENSG00000167207 NOD2 prostate glandular cells Low Enhanced Q9HC29 +ENSG00000167258 CDK12 epididymis glandular cells High Supported Q9NYV4 +ENSG00000167258 CDK12 prostate glandular cells High Supported Q9NYV4 +ENSG00000167258 CDK12 seminal vesicle glandular cells Medium Supported Q9NYV4 +ENSG00000167258 CDK12 testis cells in seminiferous ducts High Supported Q9NYV4 +ENSG00000167258 CDK12 testis Leydig cells High Supported Q9NYV4 +ENSG00000167264 DUS2 epididymis glandular cells Low Enhanced Q9NX74 +ENSG00000167264 DUS2 prostate glandular cells Low Enhanced Q9NX74 +ENSG00000167264 DUS2 seminal vesicle glandular cells Low Enhanced Q9NX74 +ENSG00000167264 DUS2 testis cells in seminiferous ducts Medium Enhanced Q9NX74 +ENSG00000167264 DUS2 testis Leydig cells High Enhanced Q9NX74 +ENSG00000167306 MYO5B epididymis glandular cells High Enhanced Q9ULV0 +ENSG00000167306 MYO5B prostate glandular cells Medium Enhanced Q9ULV0 +ENSG00000167306 MYO5B seminal vesicle glandular cells High Enhanced Q9ULV0 +ENSG00000167306 MYO5B testis cells in seminiferous ducts Low Enhanced Q9ULV0 +ENSG00000167306 MYO5B testis Leydig cells Low Enhanced Q9ULV0 +ENSG00000167315 ACAA2 epididymis glandular cells Low Enhanced P42765 +ENSG00000167315 ACAA2 seminal vesicle glandular cells Medium Enhanced P42765 +ENSG00000167315 ACAA2 testis cells in seminiferous ducts Low Enhanced P42765 +ENSG00000167315 ACAA2 testis Leydig cells High Enhanced P42765 +ENSG00000167323 STIM1 epididymis glandular cells Medium Enhanced Q13586 +ENSG00000167323 STIM1 prostate glandular cells Medium Enhanced Q13586 +ENSG00000167323 STIM1 seminal vesicle glandular cells Medium Enhanced Q13586 +ENSG00000167323 STIM1 testis cells in seminiferous ducts Medium Enhanced Q13586 +ENSG00000167323 STIM1 testis Leydig cells Low Enhanced Q13586 +ENSG00000167325 RRM1 epididymis glandular cells Medium Enhanced P23921 +ENSG00000167325 RRM1 testis cells in seminiferous ducts Low Enhanced P23921 +ENSG00000167325 RRM1 testis Leydig cells High Enhanced P23921 +ENSG00000167378 IRGQ epididymis glandular cells Medium Enhanced Q8WZA9 +ENSG00000167378 IRGQ prostate glandular cells Medium Enhanced Q8WZA9 +ENSG00000167378 IRGQ seminal vesicle glandular cells Low Enhanced Q8WZA9 +ENSG00000167378 IRGQ testis cells in seminiferous ducts Low Enhanced Q8WZA9 +ENSG00000167378 IRGQ testis Leydig cells Medium Enhanced Q8WZA9 +ENSG00000167468 GPX4 epididymis glandular cells Medium Enhanced P36969 +ENSG00000167468 GPX4 testis cells in seminiferous ducts High Enhanced P36969 +ENSG00000167468 GPX4 testis Leydig cells Medium Enhanced P36969 +ENSG00000167491 GATAD2A epididymis glandular cells Medium Enhanced Q86YP4 +ENSG00000167491 GATAD2A prostate glandular cells Low Enhanced Q86YP4 +ENSG00000167491 GATAD2A seminal vesicle glandular cells Medium Enhanced Q86YP4 +ENSG00000167491 GATAD2A testis cells in seminiferous ducts High Enhanced Q86YP4 +ENSG00000167491 GATAD2A testis Leydig cells Low Enhanced Q86YP4 +ENSG00000167523 SPATA33 epididymis glandular cells Low Enhanced Q96N06 +ENSG00000167523 SPATA33 prostate glandular cells Medium Enhanced Q96N06 +ENSG00000167523 SPATA33 seminal vesicle glandular cells Low Enhanced Q96N06 +ENSG00000167523 SPATA33 testis cells in seminiferous ducts High Enhanced Q96N06 +ENSG00000167523 SPATA33 testis Leydig cells Medium Enhanced Q96N06 +ENSG00000167552 TUBA1A epididymis glandular cells High Enhanced Q71U36 +ENSG00000167552 TUBA1A prostate glandular cells High Enhanced Q71U36 +ENSG00000167552 TUBA1A seminal vesicle glandular cells High Enhanced Q71U36 +ENSG00000167552 TUBA1A testis cells in seminiferous ducts High Enhanced Q71U36 +ENSG00000167552 TUBA1A testis Leydig cells Medium Enhanced Q71U36 +ENSG00000167553 TUBA1C epididymis glandular cells High Supported Q9BQE3 +ENSG00000167553 TUBA1C prostate glandular cells High Supported Q9BQE3 +ENSG00000167553 TUBA1C seminal vesicle glandular cells High Supported Q9BQE3 +ENSG00000167553 TUBA1C testis cells in seminiferous ducts High Supported Q9BQE3 +ENSG00000167553 TUBA1C testis Leydig cells Medium Supported Q9BQE3 +ENSG00000167554 ZNF610 epididymis glandular cells Medium Enhanced Q8N9Z0 +ENSG00000167554 ZNF610 seminal vesicle glandular cells Low Enhanced Q8N9Z0 +ENSG00000167554 ZNF610 testis Leydig cells Medium Enhanced Q8N9Z0 +ENSG00000167554 ZNF610 testis pachytene spermatocytes High Enhanced Q8N9Z0 +ENSG00000167554 ZNF610 testis peritubular cells Low Enhanced Q8N9Z0 +ENSG00000167554 ZNF610 testis preleptotene spermatocytes High Enhanced Q8N9Z0 +ENSG00000167554 ZNF610 testis round or early spermatids High Enhanced Q8N9Z0 +ENSG00000167554 ZNF610 testis spermatogonia High Enhanced Q8N9Z0 +ENSG00000167580 AQP2 epididymis glandular cells Low Enhanced P41181 +ENSG00000167580 AQP2 seminal vesicle glandular cells Low Enhanced P41181 +ENSG00000167588 GPD1 epididymis glandular cells Medium Enhanced P21695 +ENSG00000167588 GPD1 prostate glandular cells Medium Enhanced P21695 +ENSG00000167588 GPD1 seminal vesicle glandular cells High Enhanced P21695 +ENSG00000167588 GPD1 testis cells in seminiferous ducts Medium Enhanced P21695 +ENSG00000167588 GPD1 testis Leydig cells Medium Enhanced P21695 +ENSG00000167635 ZNF146 epididymis glandular cells High Supported Q15072 +ENSG00000167635 ZNF146 prostate glandular cells Medium Supported Q15072 +ENSG00000167635 ZNF146 seminal vesicle glandular cells Medium Supported Q15072 +ENSG00000167635 ZNF146 testis cells in seminiferous ducts High Supported Q15072 +ENSG00000167635 ZNF146 testis Leydig cells Medium Supported Q15072 +ENSG00000167641 PPP1R14A testis cells in seminiferous ducts Medium Enhanced Q96A00 +ENSG00000167641 PPP1R14A testis Leydig cells Medium Enhanced Q96A00 +ENSG00000167658 EEF2 epididymis glandular cells High Enhanced P13639 +ENSG00000167658 EEF2 prostate glandular cells High Enhanced P13639 +ENSG00000167658 EEF2 seminal vesicle glandular cells High Enhanced P13639 +ENSG00000167658 EEF2 testis cells in seminiferous ducts High Enhanced P13639 +ENSG00000167658 EEF2 testis Leydig cells High Enhanced P13639 +ENSG00000167670 CHAF1A epididymis glandular cells Medium Enhanced Q13111 +ENSG00000167670 CHAF1A prostate glandular cells Low Enhanced Q13111 +ENSG00000167670 CHAF1A seminal vesicle glandular cells Medium Enhanced Q13111 +ENSG00000167670 CHAF1A testis cells in seminiferous ducts High Enhanced Q13111 +ENSG00000167670 CHAF1A testis Leydig cells Low Enhanced Q13111 +ENSG00000167674 CTB-50L17.10 epididymis glandular cells High Enhanced Q7Z4V5 +ENSG00000167674 CTB-50L17.10 prostate glandular cells High Enhanced Q7Z4V5 +ENSG00000167674 CTB-50L17.10 seminal vesicle glandular cells High Enhanced Q7Z4V5 +ENSG00000167674 CTB-50L17.10 testis cells in seminiferous ducts High Enhanced Q7Z4V5 +ENSG00000167674 CTB-50L17.10 testis Leydig cells High Enhanced Q7Z4V5 +ENSG00000167680 SEMA6B epididymis glandular cells Low Enhanced Q9H3T3 +ENSG00000167699 GLOD4 epididymis glandular cells Medium Enhanced Q9HC38 +ENSG00000167699 GLOD4 prostate glandular cells High Enhanced Q9HC38 +ENSG00000167699 GLOD4 seminal vesicle glandular cells Medium Enhanced Q9HC38 +ENSG00000167699 GLOD4 testis cells in seminiferous ducts Medium Enhanced Q9HC38 +ENSG00000167699 GLOD4 testis Leydig cells High Enhanced Q9HC38 +ENSG00000167703 SLC43A2 epididymis glandular cells Low Enhanced NA +ENSG00000167703 SLC43A2 prostate glandular cells Medium Enhanced NA +ENSG00000167703 SLC43A2 testis Leydig cells Low Enhanced NA +ENSG00000167749 KLK4 prostate glandular cells High Enhanced Q9Y5K2 +ENSG00000167751 KLK2 prostate glandular cells High Supported P20151 +ENSG00000167778 SPRYD3 epididymis glandular cells Medium Enhanced Q8NCJ5 +ENSG00000167778 SPRYD3 prostate glandular cells Medium Enhanced Q8NCJ5 +ENSG00000167778 SPRYD3 seminal vesicle glandular cells Medium Enhanced Q8NCJ5 +ENSG00000167778 SPRYD3 testis cells in seminiferous ducts Medium Enhanced Q8NCJ5 +ENSG00000167778 SPRYD3 testis Leydig cells Medium Enhanced Q8NCJ5 +ENSG00000167799 NUDT8 epididymis glandular cells Medium Enhanced Q8WV74 +ENSG00000167799 NUDT8 prostate glandular cells Medium Enhanced Q8WV74 +ENSG00000167799 NUDT8 seminal vesicle glandular cells High Enhanced Q8WV74 +ENSG00000167799 NUDT8 testis cells in seminiferous ducts Medium Enhanced Q8WV74 +ENSG00000167799 NUDT8 testis Leydig cells Medium Enhanced Q8WV74 +ENSG00000167863 ATP5H epididymis glandular cells High Enhanced O75947 +ENSG00000167863 ATP5H prostate glandular cells Medium Enhanced O75947 +ENSG00000167863 ATP5H seminal vesicle glandular cells High Enhanced O75947 +ENSG00000167863 ATP5H testis cells in seminiferous ducts Medium Enhanced O75947 +ENSG00000167863 ATP5H testis Leydig cells High Enhanced O75947 +ENSG00000167969 ECI1 epididymis glandular cells High Enhanced P42126 +ENSG00000167969 ECI1 prostate glandular cells High Enhanced P42126 +ENSG00000167969 ECI1 seminal vesicle glandular cells High Enhanced P42126 +ENSG00000167969 ECI1 testis cells in seminiferous ducts Medium Enhanced P42126 +ENSG00000167969 ECI1 testis Leydig cells Medium Enhanced P42126 +ENSG00000167972 ABCA3 epididymis glandular cells High Enhanced Q99758 +ENSG00000167972 ABCA3 prostate glandular cells High Enhanced Q99758 +ENSG00000167972 ABCA3 seminal vesicle glandular cells High Enhanced Q99758 +ENSG00000167972 ABCA3 testis cells in seminiferous ducts High Enhanced Q99758 +ENSG00000167972 ABCA3 testis Leydig cells High Enhanced Q99758 +ENSG00000167978 SRRM2 epididymis glandular cells High Supported Q9UQ35 +ENSG00000167978 SRRM2 prostate glandular cells High Supported Q9UQ35 +ENSG00000167978 SRRM2 seminal vesicle glandular cells High Supported Q9UQ35 +ENSG00000167978 SRRM2 testis cells in seminiferous ducts High Supported Q9UQ35 +ENSG00000167978 SRRM2 testis Leydig cells High Supported Q9UQ35 +ENSG00000167985 SDHAF2 epididymis glandular cells Medium Supported Q9NX18 +ENSG00000167985 SDHAF2 prostate glandular cells Medium Supported Q9NX18 +ENSG00000167985 SDHAF2 seminal vesicle glandular cells Medium Supported Q9NX18 +ENSG00000167985 SDHAF2 testis cells in seminiferous ducts High Supported Q9NX18 +ENSG00000167985 SDHAF2 testis Leydig cells High Supported Q9NX18 +ENSG00000168003 SLC3A2 epididymis glandular cells Medium Enhanced P08195 +ENSG00000168003 SLC3A2 seminal vesicle glandular cells Low Enhanced P08195 +ENSG00000168003 SLC3A2 testis cells in seminiferous ducts Medium Enhanced P08195 +ENSG00000168026 TTC21A testis elongated or late spermatids Medium Enhanced Q8NDW8 +ENSG00000168026 TTC21A testis pachytene spermatocytes Medium Enhanced Q8NDW8 +ENSG00000168026 TTC21A testis round or early spermatids Medium Enhanced Q8NDW8 +ENSG00000168036 CTNNB1 epididymis glandular cells High Enhanced P35222 +ENSG00000168036 CTNNB1 prostate glandular cells High Enhanced P35222 +ENSG00000168036 CTNNB1 seminal vesicle glandular cells High Enhanced P35222 +ENSG00000168036 CTNNB1 testis cells in seminiferous ducts High Enhanced P35222 +ENSG00000168036 CTNNB1 testis Leydig cells Low Enhanced P35222 +ENSG00000168040 FADD epididymis glandular cells Medium Supported Q13158 +ENSG00000168040 FADD seminal vesicle glandular cells Low Supported Q13158 +ENSG00000168060 NAALADL1 testis cells in seminiferous ducts Low Enhanced Q9UQQ1 +ENSG00000168060 NAALADL1 testis Leydig cells Medium Enhanced Q9UQQ1 +ENSG00000168066 SF1 epididymis glandular cells High Supported Q15637 +ENSG00000168066 SF1 prostate glandular cells High Supported Q15637 +ENSG00000168066 SF1 seminal vesicle glandular cells High Supported Q15637 +ENSG00000168066 SF1 testis cells in seminiferous ducts High Supported Q15637 +ENSG00000168066 SF1 testis Leydig cells High Supported Q15637 +ENSG00000168067 MAP4K2 epididymis glandular cells Medium Enhanced Q12851 +ENSG00000168067 MAP4K2 prostate glandular cells Medium Enhanced Q12851 +ENSG00000168067 MAP4K2 seminal vesicle glandular cells Medium Enhanced Q12851 +ENSG00000168067 MAP4K2 testis cells in seminiferous ducts Medium Enhanced Q12851 +ENSG00000168067 MAP4K2 testis Leydig cells Low Enhanced Q12851 +ENSG00000168078 PBK testis cells in seminiferous ducts High Enhanced Q96KB5 +ENSG00000168116 KIAA1586 seminal vesicle glandular cells High Enhanced Q9HCI6 +ENSG00000168116 KIAA1586 testis cells in seminiferous ducts Low Enhanced Q9HCI6 +ENSG00000168143 FAM83B prostate glandular cells Low Enhanced Q5T0W9 +ENSG00000168148 HIST3H3 epididymis glandular cells High Supported Q16695 +ENSG00000168148 HIST3H3 prostate glandular cells High Supported Q16695 +ENSG00000168148 HIST3H3 seminal vesicle glandular cells High Supported Q16695 +ENSG00000168148 HIST3H3 testis cells in seminiferous ducts High Supported Q16695 +ENSG00000168148 HIST3H3 testis Leydig cells High Supported Q16695 +ENSG00000168280 KIF5C epididymis glandular cells Low Enhanced O60282 +ENSG00000168280 KIF5C prostate glandular cells Low Enhanced O60282 +ENSG00000168280 KIF5C seminal vesicle glandular cells Low Enhanced O60282 +ENSG00000168280 KIF5C testis cells in seminiferous ducts Medium Enhanced O60282 +ENSG00000168283 BMI1 epididymis glandular cells Medium Supported P35226 +ENSG00000168283 BMI1 prostate glandular cells Medium Supported P35226 +ENSG00000168283 BMI1 seminal vesicle glandular cells Medium Supported P35226 +ENSG00000168283 BMI1 testis cells in seminiferous ducts Medium Supported P35226 +ENSG00000168283 BMI1 testis Leydig cells Low Supported P35226 +ENSG00000168286 THAP11 epididymis glandular cells Medium Supported Q96EK4 +ENSG00000168286 THAP11 prostate glandular cells Medium Supported Q96EK4 +ENSG00000168286 THAP11 seminal vesicle glandular cells Medium Supported Q96EK4 +ENSG00000168286 THAP11 testis cells in seminiferous ducts Medium Supported Q96EK4 +ENSG00000168286 THAP11 testis Leydig cells Medium Supported Q96EK4 +ENSG00000168288 MMADHC epididymis glandular cells Medium Supported Q9H3L0 +ENSG00000168288 MMADHC prostate glandular cells Medium Supported Q9H3L0 +ENSG00000168288 MMADHC seminal vesicle glandular cells Medium Supported Q9H3L0 +ENSG00000168288 MMADHC testis cells in seminiferous ducts Medium Supported Q9H3L0 +ENSG00000168288 MMADHC testis Leydig cells Medium Supported Q9H3L0 +ENSG00000168291 PDHB epididymis glandular cells Medium Enhanced P11177 +ENSG00000168291 PDHB prostate glandular cells Medium Enhanced P11177 +ENSG00000168291 PDHB seminal vesicle glandular cells High Enhanced P11177 +ENSG00000168291 PDHB testis cells in seminiferous ducts Medium Enhanced P11177 +ENSG00000168291 PDHB testis Leydig cells Medium Enhanced P11177 +ENSG00000168297 PXK epididymis glandular cells Medium Supported Q7Z7A4 +ENSG00000168297 PXK prostate glandular cells Medium Supported Q7Z7A4 +ENSG00000168297 PXK seminal vesicle glandular cells Low Supported Q7Z7A4 +ENSG00000168297 PXK testis cells in seminiferous ducts Medium Supported Q7Z7A4 +ENSG00000168297 PXK testis Leydig cells Medium Supported Q7Z7A4 +ENSG00000168298 HIST1H1E epididymis glandular cells High Supported P10412 +ENSG00000168298 HIST1H1E prostate glandular cells High Supported P10412 +ENSG00000168298 HIST1H1E seminal vesicle glandular cells High Supported P10412 +ENSG00000168298 HIST1H1E testis cells in seminiferous ducts High Supported P10412 +ENSG00000168298 HIST1H1E testis Leydig cells High Supported P10412 +ENSG00000168306 ACOX2 epididymis glandular cells Medium Enhanced Q99424 +ENSG00000168306 ACOX2 prostate glandular cells Low Enhanced Q99424 +ENSG00000168306 ACOX2 seminal vesicle glandular cells Medium Enhanced Q99424 +ENSG00000168306 ACOX2 testis cells in seminiferous ducts Medium Enhanced Q99424 +ENSG00000168306 ACOX2 testis Leydig cells Medium Enhanced Q99424 +ENSG00000168309 FAM107A epididymis glandular cells Medium Enhanced O95990 +ENSG00000168309 FAM107A prostate glandular cells Low Enhanced O95990 +ENSG00000168309 FAM107A seminal vesicle glandular cells Low Enhanced O95990 +ENSG00000168310 IRF2 epididymis glandular cells High Supported P14316 +ENSG00000168310 IRF2 prostate glandular cells Medium Supported P14316 +ENSG00000168310 IRF2 seminal vesicle glandular cells Low Supported P14316 +ENSG00000168310 IRF2 testis cells in seminiferous ducts Low Supported P14316 +ENSG00000168310 IRF2 testis Leydig cells Medium Supported P14316 +ENSG00000168385 SEPT2 epididymis glandular cells Medium Supported Q15019 +ENSG00000168385 SEPT2 prostate glandular cells Medium Supported Q15019 +ENSG00000168385 SEPT2 seminal vesicle glandular cells Medium Supported Q15019 +ENSG00000168385 SEPT2 testis cells in seminiferous ducts Medium Supported Q15019 +ENSG00000168385 SEPT2 testis Leydig cells Medium Supported Q15019 +ENSG00000168439 STIP1 epididymis glandular cells Low Enhanced P31948 +ENSG00000168439 STIP1 prostate glandular cells Medium Enhanced P31948 +ENSG00000168439 STIP1 seminal vesicle glandular cells Medium Enhanced P31948 +ENSG00000168439 STIP1 testis cells in seminiferous ducts High Enhanced P31948 +ENSG00000168439 STIP1 testis Leydig cells Low Enhanced P31948 +ENSG00000168454 TXNDC2 seminal vesicle glandular cells Low Enhanced Q86VQ3 +ENSG00000168454 TXNDC2 testis elongated or late spermatids High Enhanced Q86VQ3 +ENSG00000168454 TXNDC2 testis Leydig cells Low Enhanced Q86VQ3 +ENSG00000168454 TXNDC2 testis pachytene spermatocytes High Enhanced Q86VQ3 +ENSG00000168454 TXNDC2 testis preleptotene spermatocytes High Enhanced Q86VQ3 +ENSG00000168454 TXNDC2 testis round or early spermatids High Enhanced Q86VQ3 +ENSG00000168454 TXNDC2 testis spermatogonia High Enhanced Q86VQ3 +ENSG00000168487 BMP1 epididymis glandular cells Medium Enhanced P13497 +ENSG00000168487 BMP1 prostate glandular cells Low Enhanced P13497 +ENSG00000168487 BMP1 seminal vesicle glandular cells Medium Enhanced P13497 +ENSG00000168487 BMP1 testis cells in seminiferous ducts Low Enhanced P13497 +ENSG00000168487 BMP1 testis Leydig cells Medium Enhanced P13497 +ENSG00000168495 POLR3D epididymis glandular cells Medium Enhanced P05423 +ENSG00000168495 POLR3D prostate glandular cells Medium Enhanced P05423 +ENSG00000168495 POLR3D seminal vesicle glandular cells Medium Enhanced P05423 +ENSG00000168495 POLR3D testis cells in seminiferous ducts Medium Enhanced P05423 +ENSG00000168495 POLR3D testis Leydig cells Medium Enhanced P05423 +ENSG00000168496 FEN1 epididymis glandular cells High Enhanced P39748 +ENSG00000168496 FEN1 prostate glandular cells Low Enhanced P39748 +ENSG00000168496 FEN1 seminal vesicle glandular cells Low Enhanced P39748 +ENSG00000168496 FEN1 testis cells in seminiferous ducts High Enhanced P39748 +ENSG00000168496 FEN1 testis Leydig cells Medium Enhanced P39748 +ENSG00000168497 SDPR epididymis glandular cells Low Enhanced O95810 +ENSG00000168497 SDPR seminal vesicle glandular cells Medium Enhanced O95810 +ENSG00000168497 SDPR testis Leydig cells Low Enhanced O95810 +ENSG00000168517 HEXIM2 epididymis glandular cells High Enhanced Q96MH2 +ENSG00000168517 HEXIM2 prostate glandular cells Medium Enhanced Q96MH2 +ENSG00000168517 HEXIM2 seminal vesicle glandular cells High Enhanced Q96MH2 +ENSG00000168517 HEXIM2 testis cells in seminiferous ducts High Enhanced Q96MH2 +ENSG00000168517 HEXIM2 testis Leydig cells High Enhanced Q96MH2 +ENSG00000168528 SERINC2 epididymis glandular cells Medium Enhanced Q96SA4 +ENSG00000168528 SERINC2 prostate glandular cells Medium Enhanced Q96SA4 +ENSG00000168528 SERINC2 seminal vesicle glandular cells Medium Enhanced Q96SA4 +ENSG00000168528 SERINC2 testis cells in seminiferous ducts Medium Enhanced Q96SA4 +ENSG00000168528 SERINC2 testis Leydig cells Medium Enhanced Q96SA4 +ENSG00000168539 CHRM1 testis cells in seminiferous ducts Low Enhanced P11229 +ENSG00000168556 ING2 epididymis glandular cells Medium Enhanced Q9H160 +ENSG00000168556 ING2 prostate glandular cells Medium Enhanced Q9H160 +ENSG00000168556 ING2 seminal vesicle glandular cells Medium Enhanced Q9H160 +ENSG00000168556 ING2 testis cells in seminiferous ducts Low Enhanced Q9H160 +ENSG00000168556 ING2 testis Leydig cells Medium Enhanced Q9H160 +ENSG00000168610 STAT3 epididymis glandular cells Medium Supported P40763 +ENSG00000168610 STAT3 seminal vesicle glandular cells Medium Supported P40763 +ENSG00000168610 STAT3 testis cells in seminiferous ducts Medium Supported P40763 +ENSG00000168610 STAT3 testis Leydig cells Medium Supported P40763 +ENSG00000168621 GDNF testis Leydig cells Low Supported P39905 +ENSG00000168653 NDUFS5 epididymis glandular cells Medium Supported O43920 +ENSG00000168653 NDUFS5 prostate glandular cells High Supported O43920 +ENSG00000168653 NDUFS5 seminal vesicle glandular cells High Supported O43920 +ENSG00000168653 NDUFS5 testis cells in seminiferous ducts Low Supported O43920 +ENSG00000168653 NDUFS5 testis Leydig cells High Supported O43920 +ENSG00000168701 TMEM208 epididymis glandular cells Medium Supported Q9BTX3 +ENSG00000168701 TMEM208 prostate glandular cells Low Supported Q9BTX3 +ENSG00000168701 TMEM208 seminal vesicle glandular cells Medium Supported Q9BTX3 +ENSG00000168701 TMEM208 testis cells in seminiferous ducts Medium Supported Q9BTX3 +ENSG00000168701 TMEM208 testis Leydig cells Medium Supported Q9BTX3 +ENSG00000168743 NPNT epididymis glandular cells Low Supported Q6UXI9 +ENSG00000168743 NPNT prostate glandular cells Low Supported Q6UXI9 +ENSG00000168743 NPNT testis Leydig cells Low Supported Q6UXI9 +ENSG00000168757 TSPY2 testis preleptotene spermatocytes High Supported A6NKD2 +ENSG00000168757 TSPY2 testis spermatogonia High Supported A6NKD2 +ENSG00000168763 CNNM3 epididymis glandular cells Medium Supported Q8NE01 +ENSG00000168763 CNNM3 prostate glandular cells Medium Supported Q8NE01 +ENSG00000168763 CNNM3 seminal vesicle glandular cells Medium Supported Q8NE01 +ENSG00000168763 CNNM3 testis cells in seminiferous ducts High Supported Q8NE01 +ENSG00000168763 CNNM3 testis Leydig cells High Supported Q8NE01 +ENSG00000168769 TET2 epididymis glandular cells Medium Supported Q6N021 +ENSG00000168769 TET2 prostate glandular cells Medium Supported Q6N021 +ENSG00000168769 TET2 seminal vesicle glandular cells Medium Supported Q6N021 +ENSG00000168769 TET2 testis cells in seminiferous ducts High Supported Q6N021 +ENSG00000168769 TET2 testis Leydig cells High Supported Q6N021 +ENSG00000168778 TCTN2 epididymis glandular cells Medium Enhanced Q96GX1 +ENSG00000168778 TCTN2 testis cells in seminiferous ducts Medium Enhanced Q96GX1 +ENSG00000168778 TCTN2 testis Leydig cells Low Enhanced Q96GX1 +ENSG00000168827 GFM1 epididymis glandular cells High Enhanced Q96RP9 +ENSG00000168827 GFM1 prostate glandular cells Low Enhanced Q96RP9 +ENSG00000168827 GFM1 seminal vesicle glandular cells Medium Enhanced Q96RP9 +ENSG00000168827 GFM1 testis cells in seminiferous ducts High Enhanced Q96RP9 +ENSG00000168827 GFM1 testis Leydig cells High Enhanced Q96RP9 +ENSG00000168884 TNIP2 epididymis glandular cells Medium Supported Q8NFZ5 +ENSG00000168884 TNIP2 prostate glandular cells Medium Supported Q8NFZ5 +ENSG00000168884 TNIP2 seminal vesicle glandular cells Medium Supported Q8NFZ5 +ENSG00000168884 TNIP2 testis cells in seminiferous ducts Medium Supported Q8NFZ5 +ENSG00000168884 TNIP2 testis Leydig cells Medium Supported Q8NFZ5 +ENSG00000168899 VAMP5 prostate glandular cells High Supported O95183 +ENSG00000168899 VAMP5 seminal vesicle glandular cells Low Supported O95183 +ENSG00000168899 VAMP5 testis cells in seminiferous ducts Medium Supported O95183 +ENSG00000168899 VAMP5 testis Leydig cells Low Supported O95183 +ENSG00000168907 PLA2G4F seminal vesicle glandular cells Low Enhanced Q68DD2 +ENSG00000168924 LETM1 epididymis glandular cells Low Enhanced O95202 +ENSG00000168924 LETM1 prostate glandular cells Low Enhanced O95202 +ENSG00000168924 LETM1 seminal vesicle glandular cells Medium Enhanced O95202 +ENSG00000168924 LETM1 testis cells in seminiferous ducts Medium Enhanced O95202 +ENSG00000168924 LETM1 testis Leydig cells Medium Enhanced O95202 +ENSG00000169020 ATP5I epididymis glandular cells High Supported P56385 +ENSG00000169020 ATP5I prostate glandular cells High Supported P56385 +ENSG00000169020 ATP5I seminal vesicle glandular cells Medium Supported P56385 +ENSG00000169020 ATP5I testis cells in seminiferous ducts Medium Supported P56385 +ENSG00000169020 ATP5I testis Leydig cells High Supported P56385 +ENSG00000169021 UQCRFS1 epididymis glandular cells High Enhanced P47985 +ENSG00000169021 UQCRFS1 prostate glandular cells High Enhanced P47985 +ENSG00000169021 UQCRFS1 seminal vesicle glandular cells High Enhanced P47985 +ENSG00000169021 UQCRFS1 testis cells in seminiferous ducts High Enhanced P47985 +ENSG00000169021 UQCRFS1 testis Leydig cells High Enhanced P47985 +ENSG00000169045 HNRNPH1 epididymis glandular cells High Supported P31943 +ENSG00000169045 HNRNPH1 prostate glandular cells High Supported P31943 +ENSG00000169045 HNRNPH1 seminal vesicle glandular cells High Supported P31943 +ENSG00000169045 HNRNPH1 testis cells in seminiferous ducts High Supported P31943 +ENSG00000169045 HNRNPH1 testis Leydig cells Medium Supported P31943 +ENSG00000169057 MECP2 epididymis glandular cells High Enhanced P51608 +ENSG00000169057 MECP2 prostate glandular cells High Enhanced P51608 +ENSG00000169057 MECP2 seminal vesicle glandular cells High Enhanced P51608 +ENSG00000169057 MECP2 testis cells in seminiferous ducts High Enhanced P51608 +ENSG00000169057 MECP2 testis Leydig cells High Enhanced P51608 +ENSG00000169059 VCX3A testis elongated or late spermatids Medium Supported Q9NNX9 +ENSG00000169059 VCX3A testis pachytene spermatocytes High Supported Q9NNX9 +ENSG00000169059 VCX3A testis preleptotene spermatocytes High Supported Q9NNX9 +ENSG00000169059 VCX3A testis round or early spermatids High Supported Q9NNX9 +ENSG00000169059 VCX3A testis spermatogonia High Supported Q9NNX9 +ENSG00000169064 ZBBX testis elongated or late spermatids Medium Enhanced A8MT70 +ENSG00000169064 ZBBX testis pachytene spermatocytes Low Enhanced A8MT70 +ENSG00000169064 ZBBX testis round or early spermatids Low Enhanced A8MT70 +ENSG00000169064 ZBBX testis sertoli cells Medium Enhanced A8MT70 +ENSG00000169083 AR epididymis glandular cells High Enhanced P10275 +ENSG00000169083 AR seminal vesicle glandular cells High Enhanced P10275 +ENSG00000169083 AR testis cells in seminiferous ducts Medium Enhanced P10275 +ENSG00000169083 AR testis Leydig cells Medium Enhanced P10275 +ENSG00000169093 ASMTL epididymis glandular cells High Enhanced O95671 +ENSG00000169093 ASMTL prostate glandular cells High Enhanced O95671 +ENSG00000169093 ASMTL seminal vesicle glandular cells High Enhanced O95671 +ENSG00000169093 ASMTL testis cells in seminiferous ducts High Enhanced O95671 +ENSG00000169093 ASMTL testis Leydig cells High Enhanced O95671 +ENSG00000169189 NSMCE1 prostate glandular cells Medium Enhanced Q8WV22 +ENSG00000169189 NSMCE1 testis cells in seminiferous ducts Medium Enhanced Q8WV22 +ENSG00000169189 NSMCE1 testis Leydig cells Low Enhanced Q8WV22 +ENSG00000169213 RAB3B prostate glandular cells High Enhanced P20337 +ENSG00000169217 CD2BP2 epididymis glandular cells Medium Enhanced O95400 +ENSG00000169217 CD2BP2 prostate glandular cells Medium Enhanced O95400 +ENSG00000169217 CD2BP2 seminal vesicle glandular cells Medium Enhanced O95400 +ENSG00000169217 CD2BP2 testis cells in seminiferous ducts Medium Enhanced O95400 +ENSG00000169217 CD2BP2 testis Leydig cells Medium Enhanced O95400 +ENSG00000169220 RGS14 epididymis glandular cells Low Enhanced O43566 +ENSG00000169220 RGS14 prostate glandular cells Low Enhanced O43566 +ENSG00000169220 RGS14 seminal vesicle glandular cells Medium Enhanced O43566 +ENSG00000169220 RGS14 testis cells in seminiferous ducts Medium Enhanced O43566 +ENSG00000169220 RGS14 testis Leydig cells Medium Enhanced O43566 +ENSG00000169288 MRPL1 epididymis glandular cells Medium Supported Q9BYD6 +ENSG00000169288 MRPL1 prostate glandular cells Medium Supported Q9BYD6 +ENSG00000169288 MRPL1 seminal vesicle glandular cells High Supported Q9BYD6 +ENSG00000169288 MRPL1 testis cells in seminiferous ducts Medium Supported Q9BYD6 +ENSG00000169288 MRPL1 testis Leydig cells High Supported Q9BYD6 +ENSG00000169375 SIN3A epididymis glandular cells Medium Enhanced Q96ST3 +ENSG00000169375 SIN3A prostate glandular cells Medium Enhanced Q96ST3 +ENSG00000169375 SIN3A seminal vesicle glandular cells Medium Enhanced Q96ST3 +ENSG00000169375 SIN3A testis cells in seminiferous ducts High Enhanced Q96ST3 +ENSG00000169375 SIN3A testis Leydig cells Low Enhanced Q96ST3 +ENSG00000169379 ARL13B epididymis glandular cells Medium Enhanced Q3SXY8 +ENSG00000169379 ARL13B prostate glandular cells Medium Enhanced Q3SXY8 +ENSG00000169379 ARL13B seminal vesicle glandular cells Medium Enhanced Q3SXY8 +ENSG00000169379 ARL13B testis cells in seminiferous ducts Medium Enhanced Q3SXY8 +ENSG00000169379 ARL13B testis Leydig cells Medium Enhanced Q3SXY8 +ENSG00000169393 ELSPBP1 epididymis glandular cells Medium Enhanced Q96BH3 +ENSG00000169402 RSPH10B2 testis elongated or late spermatids High Supported B2RC85 +ENSG00000169402 RSPH10B2 testis pachytene spermatocytes Low Supported B2RC85 +ENSG00000169402 RSPH10B2 testis round or early spermatids Medium Supported B2RC85 +ENSG00000169429 CXCL8 epididymis glandular cells Low Supported P10145 +ENSG00000169429 CXCL8 testis cells in seminiferous ducts Low Supported P10145 +ENSG00000169436 COL22A1 epididymis glandular cells Low Supported Q8NFW1 +ENSG00000169436 COL22A1 testis cells in seminiferous ducts Low Supported Q8NFW1 +ENSG00000169504 CLIC4 epididymis glandular cells Medium Enhanced Q9Y696 +ENSG00000169504 CLIC4 seminal vesicle glandular cells Low Enhanced Q9Y696 +ENSG00000169504 CLIC4 testis Leydig cells Low Enhanced Q9Y696 +ENSG00000169564 PCBP1 epididymis glandular cells Medium Supported Q15365 +ENSG00000169564 PCBP1 prostate glandular cells Medium Supported Q15365 +ENSG00000169564 PCBP1 seminal vesicle glandular cells Medium Supported Q15365 +ENSG00000169564 PCBP1 testis cells in seminiferous ducts High Supported Q15365 +ENSG00000169564 PCBP1 testis Leydig cells High Supported Q15365 +ENSG00000169583 CLIC3 epididymis glandular cells Medium Enhanced O95833 +ENSG00000169583 CLIC3 testis Leydig cells Low Enhanced O95833 +ENSG00000169612 FAM103A1 epididymis glandular cells High Enhanced Q9BTL3 +ENSG00000169612 FAM103A1 prostate glandular cells High Enhanced Q9BTL3 +ENSG00000169612 FAM103A1 seminal vesicle glandular cells High Enhanced Q9BTL3 +ENSG00000169612 FAM103A1 testis cells in seminiferous ducts High Enhanced Q9BTL3 +ENSG00000169612 FAM103A1 testis Leydig cells High Enhanced Q9BTL3 +ENSG00000169627 BOLA2B epididymis glandular cells Low Supported H3BPT9 +ENSG00000169627 BOLA2B prostate glandular cells Low Supported H3BPT9 +ENSG00000169627 BOLA2B seminal vesicle glandular cells Medium Supported H3BPT9 +ENSG00000169627 BOLA2B testis cells in seminiferous ducts Medium Supported H3BPT9 +ENSG00000169627 BOLA2B testis Leydig cells Medium Supported H3BPT9 +ENSG00000169641 LUZP1 epididymis glandular cells High Enhanced Q86V48 +ENSG00000169641 LUZP1 prostate glandular cells Medium Enhanced Q86V48 +ENSG00000169641 LUZP1 seminal vesicle glandular cells Medium Enhanced Q86V48 +ENSG00000169641 LUZP1 testis cells in seminiferous ducts Medium Enhanced Q86V48 +ENSG00000169641 LUZP1 testis Leydig cells Medium Enhanced Q86V48 +ENSG00000169682 SPNS1 epididymis glandular cells Low Enhanced Q9H2V7 +ENSG00000169682 SPNS1 prostate glandular cells Low Enhanced Q9H2V7 +ENSG00000169682 SPNS1 seminal vesicle glandular cells Medium Enhanced Q9H2V7 +ENSG00000169682 SPNS1 testis cells in seminiferous ducts Low Enhanced Q9H2V7 +ENSG00000169682 SPNS1 testis Leydig cells Medium Enhanced Q9H2V7 +ENSG00000169683 LRRC45 epididymis glandular cells Medium Enhanced Q96CN5 +ENSG00000169683 LRRC45 prostate glandular cells Low Enhanced Q96CN5 +ENSG00000169683 LRRC45 seminal vesicle glandular cells Medium Enhanced Q96CN5 +ENSG00000169683 LRRC45 testis cells in seminiferous ducts Medium Enhanced Q96CN5 +ENSG00000169683 LRRC45 testis Leydig cells Medium Enhanced Q96CN5 +ENSG00000169717 ACTRT2 testis elongated or late spermatids High Enhanced Q8TDY3 +ENSG00000169717 ACTRT2 testis pachytene spermatocytes Medium Enhanced Q8TDY3 +ENSG00000169717 ACTRT2 testis preleptotene spermatocytes Medium Enhanced Q8TDY3 +ENSG00000169717 ACTRT2 testis round or early spermatids High Enhanced Q8TDY3 +ENSG00000169717 ACTRT2 testis sertoli cells Low Enhanced Q8TDY3 +ENSG00000169717 ACTRT2 testis spermatogonia Medium Enhanced Q8TDY3 +ENSG00000169738 DCXR epididymis glandular cells High Enhanced Q7Z4W1 +ENSG00000169738 DCXR prostate glandular cells Medium Enhanced Q7Z4W1 +ENSG00000169738 DCXR seminal vesicle glandular cells Medium Enhanced Q7Z4W1 +ENSG00000169738 DCXR testis cells in seminiferous ducts Medium Enhanced Q7Z4W1 +ENSG00000169738 DCXR testis Leydig cells Medium Enhanced Q7Z4W1 +ENSG00000169744 LDB2 epididymis glandular cells Medium Supported O43679 +ENSG00000169744 LDB2 prostate glandular cells High Supported O43679 +ENSG00000169744 LDB2 seminal vesicle glandular cells Medium Supported O43679 +ENSG00000169744 LDB2 testis cells in seminiferous ducts High Supported O43679 +ENSG00000169744 LDB2 testis Leydig cells Medium Supported O43679 +ENSG00000169764 UGP2 testis Leydig cells Low Enhanced Q16851 +ENSG00000169800 RBMY1F testis cells in seminiferous ducts Medium Supported J3KQ82 +ENSG00000169800 RBMY1F testis pachytene spermatocytes High Supported J3KQ82 +ENSG00000169800 RBMY1F testis preleptotene spermatocytes High Supported J3KQ82 +ENSG00000169800 RBMY1F testis round or early spermatids High Supported J3KQ82 +ENSG00000169800 RBMY1F testis spermatogonia High Supported J3KQ82 +ENSG00000169813 HNRNPF epididymis glandular cells High Supported P52597 +ENSG00000169813 HNRNPF prostate glandular cells High Supported P52597 +ENSG00000169813 HNRNPF seminal vesicle glandular cells High Supported P52597 +ENSG00000169813 HNRNPF testis cells in seminiferous ducts High Supported P52597 +ENSG00000169813 HNRNPF testis Leydig cells Medium Supported P52597 +ENSG00000169860 P2RY1 epididymis glandular cells Low Enhanced P47900 +ENSG00000169860 P2RY1 prostate glandular cells Medium Enhanced P47900 +ENSG00000169860 P2RY1 seminal vesicle glandular cells Low Enhanced P47900 +ENSG00000169860 P2RY1 testis cells in seminiferous ducts Low Enhanced P47900 +ENSG00000169860 P2RY1 testis Leydig cells Low Enhanced P47900 +ENSG00000169957 ZNF768 epididymis glandular cells High Supported Q9H5H4 +ENSG00000169957 ZNF768 prostate glandular cells Medium Supported Q9H5H4 +ENSG00000169957 ZNF768 seminal vesicle glandular cells Medium Supported Q9H5H4 +ENSG00000169957 ZNF768 testis cells in seminiferous ducts High Supported Q9H5H4 +ENSG00000169957 ZNF768 testis Leydig cells Low Supported Q9H5H4 +ENSG00000170004 CHD3 epididymis glandular cells Medium Supported Q12873 +ENSG00000170004 CHD3 prostate glandular cells Medium Supported Q12873 +ENSG00000170004 CHD3 testis cells in seminiferous ducts Medium Supported Q12873 +ENSG00000170004 CHD3 testis Leydig cells Medium Supported Q12873 +ENSG00000170088 TMEM192 epididymis glandular cells Medium Enhanced Q8IY95 +ENSG00000170088 TMEM192 prostate glandular cells Medium Enhanced Q8IY95 +ENSG00000170088 TMEM192 seminal vesicle glandular cells Medium Enhanced Q8IY95 +ENSG00000170088 TMEM192 testis cells in seminiferous ducts Medium Enhanced Q8IY95 +ENSG00000170088 TMEM192 testis Leydig cells Medium Enhanced Q8IY95 +ENSG00000170144 HNRNPA3 epididymis glandular cells High Supported P51991 +ENSG00000170144 HNRNPA3 prostate glandular cells High Supported P51991 +ENSG00000170144 HNRNPA3 seminal vesicle glandular cells High Supported P51991 +ENSG00000170144 HNRNPA3 testis cells in seminiferous ducts High Supported P51991 +ENSG00000170144 HNRNPA3 testis Leydig cells Medium Supported P51991 +ENSG00000170242 USP47 epididymis glandular cells Medium Supported Q96K76 +ENSG00000170242 USP47 prostate glandular cells High Supported Q96K76 +ENSG00000170242 USP47 seminal vesicle glandular cells Medium Supported Q96K76 +ENSG00000170242 USP47 testis cells in seminiferous ducts Medium Supported Q96K76 +ENSG00000170242 USP47 testis Leydig cells High Supported Q96K76 +ENSG00000170264 FAM161A epididymis glandular cells Low Enhanced Q3B820 +ENSG00000170265 ZNF282 epididymis glandular cells Medium Supported Q9UDV7 +ENSG00000170265 ZNF282 prostate glandular cells Medium Supported Q9UDV7 +ENSG00000170265 ZNF282 seminal vesicle glandular cells Medium Supported Q9UDV7 +ENSG00000170265 ZNF282 testis cells in seminiferous ducts High Supported Q9UDV7 +ENSG00000170265 ZNF282 testis Leydig cells High Supported Q9UDV7 +ENSG00000170266 GLB1 epididymis glandular cells Medium Enhanced P16278 +ENSG00000170266 GLB1 prostate glandular cells Medium Enhanced P16278 +ENSG00000170266 GLB1 seminal vesicle glandular cells High Enhanced P16278 +ENSG00000170266 GLB1 testis cells in seminiferous ducts Medium Enhanced P16278 +ENSG00000170266 GLB1 testis Leydig cells High Enhanced P16278 +ENSG00000170312 CDK1 epididymis glandular cells Medium Enhanced P06493 +ENSG00000170312 CDK1 prostate glandular cells Medium Enhanced P06493 +ENSG00000170312 CDK1 testis cells in seminiferous ducts High Enhanced P06493 +ENSG00000170315 UBB epididymis glandular cells Medium Supported P0CG47 +ENSG00000170315 UBB prostate glandular cells High Supported P0CG47 +ENSG00000170315 UBB seminal vesicle glandular cells Medium Supported P0CG47 +ENSG00000170315 UBB testis cells in seminiferous ducts High Supported P0CG47 +ENSG00000170315 UBB testis Leydig cells Medium Supported P0CG47 +ENSG00000170348 TMED10 epididymis glandular cells High Enhanced P49755 +ENSG00000170348 TMED10 prostate glandular cells Medium Enhanced P49755 +ENSG00000170348 TMED10 seminal vesicle glandular cells High Enhanced P49755 +ENSG00000170348 TMED10 testis cells in seminiferous ducts Medium Enhanced P49755 +ENSG00000170348 TMED10 testis Leydig cells Medium Enhanced P49755 +ENSG00000170370 EMX2 epididymis glandular cells Medium Enhanced Q04743 +ENSG00000170370 EMX2 seminal vesicle glandular cells Medium Enhanced Q04743 +ENSG00000170374 SP7 testis elongated or late spermatids Medium Enhanced Q8TDD2 +ENSG00000170374 SP7 testis pachytene spermatocytes Medium Enhanced Q8TDD2 +ENSG00000170374 SP7 testis preleptotene spermatocytes High Enhanced Q8TDD2 +ENSG00000170374 SP7 testis round or early spermatids Low Enhanced Q8TDD2 +ENSG00000170374 SP7 testis spermatogonia High Enhanced Q8TDD2 +ENSG00000170412 GPRC5C epididymis glandular cells Low Enhanced Q9NQ84 +ENSG00000170412 GPRC5C prostate glandular cells Medium Enhanced Q9NQ84 +ENSG00000170412 GPRC5C seminal vesicle glandular cells Medium Enhanced Q9NQ84 +ENSG00000170412 GPRC5C testis cells in seminiferous ducts Medium Enhanced Q9NQ84 +ENSG00000170412 GPRC5C testis Leydig cells Medium Enhanced Q9NQ84 +ENSG00000170421 KRT8 epididymis glandular cells High Enhanced P05787 +ENSG00000170421 KRT8 prostate glandular cells High Enhanced P05787 +ENSG00000170421 KRT8 seminal vesicle glandular cells High Enhanced P05787 +ENSG00000170430 MGMT epididymis glandular cells High Supported P16455 +ENSG00000170430 MGMT prostate glandular cells Medium Supported P16455 +ENSG00000170430 MGMT seminal vesicle glandular cells High Supported P16455 +ENSG00000170430 MGMT testis cells in seminiferous ducts High Supported P16455 +ENSG00000170430 MGMT testis Leydig cells Medium Supported P16455 +ENSG00000170439 METTL7B epididymis glandular cells High Enhanced Q6UX53 +ENSG00000170458 CD14 testis cells in seminiferous ducts Low Enhanced P08571 +ENSG00000170458 CD14 testis Leydig cells Low Enhanced P08571 +ENSG00000170469 SPATA24 testis cells in seminiferous ducts Medium Enhanced Q86W54 +ENSG00000170473 PYM1 epididymis glandular cells Medium Supported Q9BRP8 +ENSG00000170473 PYM1 prostate glandular cells Medium Supported Q9BRP8 +ENSG00000170473 PYM1 seminal vesicle glandular cells Medium Supported Q9BRP8 +ENSG00000170473 PYM1 testis cells in seminiferous ducts High Supported Q9BRP8 +ENSG00000170473 PYM1 testis Leydig cells Medium Supported Q9BRP8 +ENSG00000170515 PA2G4 epididymis glandular cells Medium Supported Q9UQ80 +ENSG00000170515 PA2G4 prostate glandular cells High Supported Q9UQ80 +ENSG00000170515 PA2G4 seminal vesicle glandular cells Medium Supported Q9UQ80 +ENSG00000170515 PA2G4 testis cells in seminiferous ducts Medium Supported Q9UQ80 +ENSG00000170515 PA2G4 testis Leydig cells Medium Supported Q9UQ80 +ENSG00000170545 SMAGP epididymis glandular cells High Enhanced Q0VAQ4 +ENSG00000170545 SMAGP prostate glandular cells Medium Enhanced Q0VAQ4 +ENSG00000170545 SMAGP seminal vesicle glandular cells Low Enhanced Q0VAQ4 +ENSG00000170545 SMAGP testis cells in seminiferous ducts Medium Enhanced Q0VAQ4 +ENSG00000170545 SMAGP testis Leydig cells Medium Enhanced Q0VAQ4 +ENSG00000170558 CDH2 epididymis glandular cells Medium Enhanced P19022 +ENSG00000170558 CDH2 testis cells in seminiferous ducts High Enhanced P19022 +ENSG00000170613 FAM71B testis elongated or late spermatids High Enhanced Q8TC56 +ENSG00000170613 FAM71B testis round or early spermatids High Enhanced Q8TC56 +ENSG00000170632 ARMC10 epididymis glandular cells Medium Enhanced Q8N2F6 +ENSG00000170632 ARMC10 prostate glandular cells Medium Enhanced Q8N2F6 +ENSG00000170632 ARMC10 seminal vesicle glandular cells Medium Enhanced Q8N2F6 +ENSG00000170632 ARMC10 testis cells in seminiferous ducts Medium Enhanced Q8N2F6 +ENSG00000170632 ARMC10 testis Leydig cells Medium Enhanced Q8N2F6 +ENSG00000170748 RBMXL2 testis pachytene spermatocytes High Enhanced O75526 +ENSG00000170748 RBMXL2 testis preleptotene spermatocytes High Enhanced O75526 +ENSG00000170748 RBMXL2 testis round or early spermatids High Enhanced O75526 +ENSG00000170748 RBMXL2 testis spermatogonia High Enhanced O75526 +ENSG00000170786 SDR16C5 testis cells in seminiferous ducts Low Enhanced Q8N3Y7 +ENSG00000170786 SDR16C5 testis Leydig cells Low Enhanced Q8N3Y7 +ENSG00000170802 FOXN2 testis Leydig cells Medium Supported P32314 +ENSG00000170854 RIOX2 epididymis glandular cells High Supported Q8IUF8 +ENSG00000170854 RIOX2 prostate glandular cells Medium Supported Q8IUF8 +ENSG00000170854 RIOX2 seminal vesicle glandular cells Medium Supported Q8IUF8 +ENSG00000170854 RIOX2 testis cells in seminiferous ducts High Supported Q8IUF8 +ENSG00000170854 RIOX2 testis Leydig cells High Supported Q8IUF8 +ENSG00000170906 NDUFA3 epididymis glandular cells Medium Supported NA +ENSG00000170906 NDUFA3 prostate glandular cells High Supported NA +ENSG00000170906 NDUFA3 seminal vesicle glandular cells High Supported NA +ENSG00000170906 NDUFA3 testis cells in seminiferous ducts High Supported NA +ENSG00000170906 NDUFA3 testis Leydig cells High Supported NA +ENSG00000170948 MBD3L1 testis elongated or late spermatids High Supported Q8WWY6 +ENSG00000170948 MBD3L1 testis round or early spermatids High Supported Q8WWY6 +ENSG00000170950 PGK2 testis cells in seminiferous ducts Medium Supported P07205 +ENSG00000170989 S1PR1 epididymis glandular cells Medium Supported P21453 +ENSG00000170989 S1PR1 seminal vesicle glandular cells Low Supported P21453 +ENSG00000170989 S1PR1 testis cells in seminiferous ducts Medium Supported P21453 +ENSG00000170989 S1PR1 testis Leydig cells Medium Supported P21453 +ENSG00000171103 TRMT61B epididymis glandular cells Medium Enhanced Q9BVS5 +ENSG00000171103 TRMT61B prostate glandular cells Medium Enhanced Q9BVS5 +ENSG00000171103 TRMT61B seminal vesicle glandular cells Medium Enhanced Q9BVS5 +ENSG00000171103 TRMT61B testis cells in seminiferous ducts Medium Enhanced Q9BVS5 +ENSG00000171103 TRMT61B testis Leydig cells Medium Enhanced Q9BVS5 +ENSG00000171115 GIMAP8 epididymis glandular cells High Supported Q8ND71 +ENSG00000171115 GIMAP8 prostate glandular cells High Supported Q8ND71 +ENSG00000171115 GIMAP8 seminal vesicle glandular cells Medium Supported Q8ND71 +ENSG00000171115 GIMAP8 testis cells in seminiferous ducts High Supported Q8ND71 +ENSG00000171115 GIMAP8 testis Leydig cells High Supported Q8ND71 +ENSG00000171124 FUT3 epididymis glandular cells Low Supported P21217 +ENSG00000171124 FUT3 seminal vesicle glandular cells Low Supported P21217 +ENSG00000171124 FUT3 testis cells in seminiferous ducts Low Supported P21217 +ENSG00000171124 FUT3 testis Leydig cells Medium Supported P21217 +ENSG00000171132 PRKCE testis cells in seminiferous ducts Medium Enhanced Q02156 +ENSG00000171174 RBKS epididymis glandular cells Medium Enhanced Q9H477 +ENSG00000171174 RBKS prostate glandular cells Low Enhanced Q9H477 +ENSG00000171174 RBKS seminal vesicle glandular cells Low Enhanced Q9H477 +ENSG00000171174 RBKS testis cells in seminiferous ducts High Enhanced Q9H477 +ENSG00000171174 RBKS testis Leydig cells Medium Enhanced Q9H477 +ENSG00000171219 CDC42BPG prostate glandular cells Low Enhanced Q6DT37 +ENSG00000171219 CDC42BPG seminal vesicle glandular cells Low Enhanced Q6DT37 +ENSG00000171219 CDC42BPG testis cells in seminiferous ducts Low Enhanced Q6DT37 +ENSG00000171219 CDC42BPG testis Leydig cells Low Enhanced Q6DT37 +ENSG00000171224 C10orf35 epididymis glandular cells High Enhanced Q96D05 +ENSG00000171224 C10orf35 seminal vesicle glandular cells Low Enhanced Q96D05 +ENSG00000171224 C10orf35 testis cells in seminiferous ducts Low Enhanced Q96D05 +ENSG00000171227 TMEM37 epididymis glandular cells Medium Enhanced Q8WXS4 +ENSG00000171227 TMEM37 seminal vesicle glandular cells Low Enhanced Q8WXS4 +ENSG00000171227 TMEM37 testis cells in seminiferous ducts Low Enhanced Q8WXS4 +ENSG00000171227 TMEM37 testis Leydig cells Medium Enhanced Q8WXS4 +ENSG00000171236 LRG1 epididymis glandular cells Low Enhanced P02750 +ENSG00000171236 LRG1 prostate glandular cells Medium Enhanced P02750 +ENSG00000171236 LRG1 seminal vesicle glandular cells Low Enhanced P02750 +ENSG00000171236 LRG1 testis cells in seminiferous ducts Medium Enhanced P02750 +ENSG00000171236 LRG1 testis Leydig cells Low Enhanced P02750 +ENSG00000171246 NPTX1 testis cells in seminiferous ducts Low Enhanced Q15818 +ENSG00000171262 FAM98B epididymis glandular cells High Enhanced Q52LJ0 +ENSG00000171262 FAM98B prostate glandular cells Medium Enhanced Q52LJ0 +ENSG00000171262 FAM98B seminal vesicle glandular cells Medium Enhanced Q52LJ0 +ENSG00000171262 FAM98B testis cells in seminiferous ducts High Enhanced Q52LJ0 +ENSG00000171262 FAM98B testis Leydig cells Medium Enhanced Q52LJ0 +ENSG00000171298 GAA epididymis glandular cells High Enhanced P10253 +ENSG00000171298 GAA prostate glandular cells High Enhanced P10253 +ENSG00000171298 GAA seminal vesicle glandular cells High Enhanced P10253 +ENSG00000171298 GAA testis cells in seminiferous ducts Medium Enhanced P10253 +ENSG00000171298 GAA testis Leydig cells Medium Enhanced P10253 +ENSG00000171302 CANT1 epididymis glandular cells Medium Enhanced Q8WVQ1 +ENSG00000171302 CANT1 prostate glandular cells High Enhanced Q8WVQ1 +ENSG00000171302 CANT1 seminal vesicle glandular cells High Enhanced Q8WVQ1 +ENSG00000171302 CANT1 testis cells in seminiferous ducts Low Enhanced Q8WVQ1 +ENSG00000171302 CANT1 testis Leydig cells Medium Enhanced Q8WVQ1 +ENSG00000171345 KRT19 epididymis glandular cells High Enhanced P08727 +ENSG00000171345 KRT19 prostate glandular cells High Enhanced P08727 +ENSG00000171345 KRT19 seminal vesicle glandular cells High Enhanced P08727 +ENSG00000171346 KRT15 prostate glandular cells Low Enhanced P19012 +ENSG00000171475 WIPF2 epididymis glandular cells Medium Enhanced Q8TF74 +ENSG00000171475 WIPF2 prostate glandular cells Medium Enhanced Q8TF74 +ENSG00000171475 WIPF2 seminal vesicle glandular cells Low Enhanced Q8TF74 +ENSG00000171475 WIPF2 testis Leydig cells Low Enhanced Q8TF74 +ENSG00000171476 HOPX epididymis glandular cells Medium Enhanced Q9BPY8 +ENSG00000171476 HOPX testis cells in seminiferous ducts Low Enhanced Q9BPY8 +ENSG00000171478 SPACA5B testis elongated or late spermatids High Supported NA +ENSG00000171478 SPACA5B testis round or early spermatids High Supported NA +ENSG00000171489 SPACA5 testis elongated or late spermatids High Supported NA +ENSG00000171489 SPACA5 testis round or early spermatids High Supported NA +ENSG00000171490 RSL1D1 epididymis glandular cells High Supported O76021 +ENSG00000171490 RSL1D1 prostate glandular cells Medium Supported O76021 +ENSG00000171490 RSL1D1 seminal vesicle glandular cells High Supported O76021 +ENSG00000171490 RSL1D1 testis cells in seminiferous ducts High Supported O76021 +ENSG00000171490 RSL1D1 testis Leydig cells High Supported O76021 +ENSG00000171495 MROH2B testis elongated or late spermatids High Supported Q7Z745 +ENSG00000171495 MROH2B testis Leydig cells Low Supported Q7Z745 +ENSG00000171495 MROH2B testis pachytene spermatocytes Low Supported Q7Z745 +ENSG00000171495 MROH2B testis preleptotene spermatocytes Low Supported Q7Z745 +ENSG00000171495 MROH2B testis round or early spermatids Low Supported Q7Z745 +ENSG00000171495 MROH2B testis spermatogonia Low Supported Q7Z745 +ENSG00000171503 ETFDH epididymis glandular cells Low Enhanced Q16134 +ENSG00000171503 ETFDH prostate glandular cells Low Enhanced Q16134 +ENSG00000171503 ETFDH seminal vesicle glandular cells Medium Enhanced Q16134 +ENSG00000171503 ETFDH testis cells in seminiferous ducts Low Enhanced Q16134 +ENSG00000171503 ETFDH testis Leydig cells Medium Enhanced Q16134 +ENSG00000171564 FGB prostate glandular cells Low Enhanced P02675 +ENSG00000171564 FGB seminal vesicle glandular cells Medium Enhanced P02675 +ENSG00000171564 FGB testis Leydig cells Low Enhanced P02675 +ENSG00000171566 PLRG1 epididymis glandular cells High Supported O43660 +ENSG00000171566 PLRG1 prostate glandular cells Medium Supported O43660 +ENSG00000171566 PLRG1 seminal vesicle glandular cells High Supported O43660 +ENSG00000171566 PLRG1 testis cells in seminiferous ducts High Supported O43660 +ENSG00000171566 PLRG1 testis Leydig cells High Supported O43660 +ENSG00000171595 DNAI2 testis elongated or late spermatids High Enhanced Q9GZS0 +ENSG00000171595 DNAI2 testis pachytene spermatocytes High Enhanced Q9GZS0 +ENSG00000171595 DNAI2 testis round or early spermatids High Enhanced Q9GZS0 +ENSG00000171608 PIK3CD epididymis glandular cells Low Enhanced O00329 +ENSG00000171608 PIK3CD testis cells in seminiferous ducts Low Enhanced O00329 +ENSG00000171681 ATF7IP epididymis glandular cells Medium Enhanced Q6VMQ6 +ENSG00000171681 ATF7IP prostate glandular cells Low Enhanced Q6VMQ6 +ENSG00000171681 ATF7IP seminal vesicle glandular cells Medium Enhanced Q6VMQ6 +ENSG00000171681 ATF7IP testis cells in seminiferous ducts Medium Enhanced Q6VMQ6 +ENSG00000171681 ATF7IP testis Leydig cells Medium Enhanced Q6VMQ6 +ENSG00000171720 HDAC3 epididymis glandular cells High Supported O15379 +ENSG00000171720 HDAC3 prostate glandular cells Medium Supported O15379 +ENSG00000171720 HDAC3 seminal vesicle glandular cells Medium Supported O15379 +ENSG00000171720 HDAC3 testis cells in seminiferous ducts Medium Supported O15379 +ENSG00000171720 HDAC3 testis Leydig cells Low Supported O15379 +ENSG00000171723 GPHN epididymis glandular cells High Enhanced Q9NQX3 +ENSG00000171723 GPHN prostate glandular cells Medium Enhanced Q9NQX3 +ENSG00000171723 GPHN seminal vesicle glandular cells Medium Enhanced Q9NQX3 +ENSG00000171723 GPHN testis cells in seminiferous ducts Medium Enhanced Q9NQX3 +ENSG00000171723 GPHN testis Leydig cells Low Enhanced Q9NQX3 +ENSG00000171766 GATM testis cells in seminiferous ducts Low Enhanced P50440 +ENSG00000171772 SYCE1 testis cells in seminiferous ducts High Enhanced Q8N0S2 +ENSG00000171791 BCL2 epididymis glandular cells High Enhanced P10415 +ENSG00000171791 BCL2 prostate glandular cells High Enhanced P10415 +ENSG00000171791 BCL2 seminal vesicle glandular cells High Enhanced P10415 +ENSG00000171793 CTPS1 epididymis glandular cells Low Enhanced P17812 +ENSG00000171793 CTPS1 seminal vesicle glandular cells Medium Enhanced P17812 +ENSG00000171793 CTPS1 testis cells in seminiferous ducts High Enhanced P17812 +ENSG00000171793 CTPS1 testis Leydig cells Medium Enhanced P17812 +ENSG00000171817 ZNF540 epididymis glandular cells Medium Supported Q8NDQ6 +ENSG00000171817 ZNF540 prostate glandular cells High Supported Q8NDQ6 +ENSG00000171817 ZNF540 seminal vesicle glandular cells High Supported Q8NDQ6 +ENSG00000171817 ZNF540 testis cells in seminiferous ducts High Supported Q8NDQ6 +ENSG00000171817 ZNF540 testis Leydig cells High Supported Q8NDQ6 +ENSG00000171824 EXOSC10 epididymis glandular cells Medium Enhanced Q01780 +ENSG00000171824 EXOSC10 prostate glandular cells Low Enhanced Q01780 +ENSG00000171824 EXOSC10 seminal vesicle glandular cells Low Enhanced Q01780 +ENSG00000171824 EXOSC10 testis cells in seminiferous ducts Medium Enhanced Q01780 +ENSG00000171824 EXOSC10 testis Leydig cells Medium Enhanced Q01780 +ENSG00000171848 RRM2 testis cells in seminiferous ducts Low Enhanced P31350 +ENSG00000171860 C3AR1 testis Leydig cells Low Enhanced Q16581 +ENSG00000171861 MRM3 epididymis glandular cells Low Enhanced Q9HC36 +ENSG00000171861 MRM3 prostate glandular cells Low Enhanced Q9HC36 +ENSG00000171861 MRM3 seminal vesicle glandular cells Medium Enhanced Q9HC36 +ENSG00000171861 MRM3 testis cells in seminiferous ducts High Enhanced Q9HC36 +ENSG00000171861 MRM3 testis Leydig cells High Enhanced Q9HC36 +ENSG00000171864 PRND testis cells in seminiferous ducts High Enhanced Q9UKY0 +ENSG00000171867 PRNP prostate glandular cells Low Enhanced P04156 +ENSG00000171867 PRNP testis cells in seminiferous ducts Low Enhanced P04156 +ENSG00000171872 KLF17 testis elongated or late spermatids High Enhanced Q5JT82 +ENSG00000171872 KLF17 testis pachytene spermatocytes Low Enhanced Q5JT82 +ENSG00000171872 KLF17 testis round or early spermatids High Enhanced Q5JT82 +ENSG00000171872 KLF17 testis spermatogonia Low Enhanced Q5JT82 +ENSG00000171903 CYP4F11 epididymis glandular cells Low Enhanced Q9HBI6 +ENSG00000171903 CYP4F11 seminal vesicle glandular cells Low Enhanced Q9HBI6 +ENSG00000171914 TLN2 seminal vesicle glandular cells Low Enhanced Q9Y4G6 +ENSG00000171914 TLN2 testis cells in seminiferous ducts Low Enhanced Q9Y4G6 +ENSG00000171951 SCG2 prostate glandular cells Low Enhanced P13521 +ENSG00000171951 SCG2 testis cells in seminiferous ducts Low Enhanced P13521 +ENSG00000171953 ATPAF2 epididymis glandular cells Medium Supported Q8N5M1 +ENSG00000171953 ATPAF2 prostate glandular cells Medium Supported Q8N5M1 +ENSG00000171953 ATPAF2 seminal vesicle glandular cells Low Supported Q8N5M1 +ENSG00000171953 ATPAF2 testis cells in seminiferous ducts Medium Supported Q8N5M1 +ENSG00000171953 ATPAF2 testis Leydig cells Medium Supported Q8N5M1 +ENSG00000171989 LDHAL6B testis elongated or late spermatids High Enhanced Q9BYZ2 +ENSG00000171989 LDHAL6B testis Leydig cells Low Enhanced Q9BYZ2 +ENSG00000171989 LDHAL6B testis pachytene spermatocytes High Enhanced Q9BYZ2 +ENSG00000171989 LDHAL6B testis round or early spermatids High Enhanced Q9BYZ2 +ENSG00000172037 LAMB2 testis cells in seminiferous ducts Low Supported P55268 +ENSG00000172053 QARS epididymis glandular cells Medium Enhanced P47897 +ENSG00000172053 QARS prostate glandular cells Medium Enhanced P47897 +ENSG00000172053 QARS seminal vesicle glandular cells Medium Enhanced P47897 +ENSG00000172053 QARS testis cells in seminiferous ducts Medium Enhanced P47897 +ENSG00000172053 QARS testis Leydig cells Medium Enhanced P47897 +ENSG00000172062 SMN1 epididymis glandular cells Medium Enhanced NA +ENSG00000172062 SMN1 prostate glandular cells Medium Enhanced NA +ENSG00000172062 SMN1 seminal vesicle glandular cells Low Enhanced NA +ENSG00000172062 SMN1 testis cells in seminiferous ducts High Enhanced NA +ENSG00000172062 SMN1 testis Leydig cells High Enhanced NA +ENSG00000172071 EIF2AK3 epididymis glandular cells High Enhanced Q9NZJ5 +ENSG00000172071 EIF2AK3 prostate glandular cells Medium Enhanced Q9NZJ5 +ENSG00000172071 EIF2AK3 seminal vesicle glandular cells High Enhanced Q9NZJ5 +ENSG00000172071 EIF2AK3 testis cells in seminiferous ducts Medium Enhanced Q9NZJ5 +ENSG00000172071 EIF2AK3 testis Leydig cells High Enhanced Q9NZJ5 +ENSG00000172073 TEX37 testis elongated or late spermatids High Enhanced Q96LM6 +ENSG00000172073 TEX37 testis pachytene spermatocytes Low Enhanced Q96LM6 +ENSG00000172073 TEX37 testis preleptotene spermatocytes High Enhanced Q96LM6 +ENSG00000172073 TEX37 testis round or early spermatids Low Enhanced Q96LM6 +ENSG00000172073 TEX37 testis spermatogonia High Enhanced Q96LM6 +ENSG00000172115 CYCS epididymis glandular cells Medium Enhanced P99999 +ENSG00000172115 CYCS prostate glandular cells High Enhanced P99999 +ENSG00000172115 CYCS seminal vesicle glandular cells High Enhanced P99999 +ENSG00000172115 CYCS testis cells in seminiferous ducts High Enhanced P99999 +ENSG00000172115 CYCS testis Leydig cells Medium Enhanced P99999 +ENSG00000172137 CALB2 testis Leydig cells High Enhanced NA +ENSG00000172175 MALT1 epididymis glandular cells Low Enhanced Q9UDY8 +ENSG00000172175 MALT1 prostate glandular cells Low Enhanced Q9UDY8 +ENSG00000172175 MALT1 testis cells in seminiferous ducts Medium Enhanced Q9UDY8 +ENSG00000172216 CEBPB epididymis glandular cells Medium Supported P17676 +ENSG00000172216 CEBPB prostate glandular cells Medium Supported P17676 +ENSG00000172216 CEBPB seminal vesicle glandular cells Medium Supported P17676 +ENSG00000172216 CEBPB testis Leydig cells Medium Supported P17676 +ENSG00000172264 MACROD2 epididymis glandular cells Medium Enhanced A1Z1Q3 +ENSG00000172264 MACROD2 prostate glandular cells Medium Enhanced A1Z1Q3 +ENSG00000172264 MACROD2 seminal vesicle glandular cells Medium Enhanced A1Z1Q3 +ENSG00000172264 MACROD2 testis cells in seminiferous ducts Medium Enhanced A1Z1Q3 +ENSG00000172264 MACROD2 testis Leydig cells Medium Enhanced A1Z1Q3 +ENSG00000172270 BSG epididymis glandular cells High Enhanced P35613 +ENSG00000172270 BSG prostate glandular cells Medium Enhanced P35613 +ENSG00000172270 BSG testis cells in seminiferous ducts High Enhanced P35613 +ENSG00000172296 SPTLC3 epididymis glandular cells High Enhanced Q9NUV7 +ENSG00000172296 SPTLC3 prostate glandular cells High Enhanced Q9NUV7 +ENSG00000172296 SPTLC3 seminal vesicle glandular cells Low Enhanced Q9NUV7 +ENSG00000172331 BPGM prostate glandular cells Medium Enhanced P07738 +ENSG00000172340 SUCLG2 epididymis glandular cells High Enhanced Q96I99 +ENSG00000172340 SUCLG2 prostate glandular cells High Enhanced Q96I99 +ENSG00000172340 SUCLG2 seminal vesicle glandular cells High Enhanced Q96I99 +ENSG00000172340 SUCLG2 testis cells in seminiferous ducts High Enhanced Q96I99 +ENSG00000172340 SUCLG2 testis Leydig cells High Enhanced Q96I99 +ENSG00000172361 CFAP53 testis cells in seminiferous ducts Low Enhanced Q96M91 +ENSG00000172379 ARNT2 seminal vesicle glandular cells Low Enhanced Q9HBZ2 +ENSG00000172379 ARNT2 testis cells in seminiferous ducts Low Enhanced Q9HBZ2 +ENSG00000172379 ARNT2 testis Leydig cells Low Enhanced Q9HBZ2 +ENSG00000172380 GNG12 epididymis glandular cells Medium Enhanced Q9UBI6 +ENSG00000172380 GNG12 prostate glandular cells Low Enhanced Q9UBI6 +ENSG00000172380 GNG12 seminal vesicle glandular cells Medium Enhanced Q9UBI6 +ENSG00000172380 GNG12 testis Leydig cells Low Enhanced Q9UBI6 +ENSG00000172409 CLP1 epididymis glandular cells Medium Supported Q92989 +ENSG00000172409 CLP1 prostate glandular cells Medium Supported Q92989 +ENSG00000172409 CLP1 seminal vesicle glandular cells Medium Supported Q92989 +ENSG00000172409 CLP1 testis cells in seminiferous ducts High Supported Q92989 +ENSG00000172409 CLP1 testis Leydig cells High Supported Q92989 +ENSG00000172426 RSPH9 testis elongated or late spermatids High Enhanced Q9H1X1 +ENSG00000172426 RSPH9 testis Leydig cells High Enhanced Q9H1X1 +ENSG00000172426 RSPH9 testis round or early spermatids High Enhanced Q9H1X1 +ENSG00000172466 ZNF24 epididymis glandular cells High Supported P17028 +ENSG00000172466 ZNF24 prostate glandular cells High Supported P17028 +ENSG00000172466 ZNF24 seminal vesicle glandular cells Medium Supported P17028 +ENSG00000172466 ZNF24 testis cells in seminiferous ducts Medium Supported P17028 +ENSG00000172466 ZNF24 testis Leydig cells Medium Supported P17028 +ENSG00000172469 MANEA epididymis glandular cells Medium Enhanced Q5SRI9 +ENSG00000172469 MANEA prostate glandular cells Low Enhanced Q5SRI9 +ENSG00000172469 MANEA seminal vesicle glandular cells Low Enhanced Q5SRI9 +ENSG00000172469 MANEA testis cells in seminiferous ducts Low Enhanced Q5SRI9 +ENSG00000172469 MANEA testis Leydig cells Low Enhanced Q5SRI9 +ENSG00000172613 RAD9A epididymis glandular cells High Enhanced Q99638 +ENSG00000172613 RAD9A prostate glandular cells High Enhanced Q99638 +ENSG00000172613 RAD9A seminal vesicle glandular cells High Enhanced Q99638 +ENSG00000172613 RAD9A testis cells in seminiferous ducts High Enhanced Q99638 +ENSG00000172613 RAD9A testis Leydig cells Low Enhanced Q99638 +ENSG00000172661 WASHC2C epididymis glandular cells Medium Supported Q9Y4E1 +ENSG00000172661 WASHC2C prostate glandular cells Medium Supported Q9Y4E1 +ENSG00000172661 WASHC2C seminal vesicle glandular cells Medium Supported Q9Y4E1 +ENSG00000172661 WASHC2C testis cells in seminiferous ducts Medium Supported Q9Y4E1 +ENSG00000172661 WASHC2C testis Leydig cells Medium Supported Q9Y4E1 +ENSG00000172667 ZMAT3 epididymis glandular cells Low Enhanced Q9HA38 +ENSG00000172667 ZMAT3 prostate glandular cells Low Enhanced Q9HA38 +ENSG00000172667 ZMAT3 seminal vesicle glandular cells Low Enhanced Q9HA38 +ENSG00000172667 ZMAT3 testis cells in seminiferous ducts Medium Enhanced Q9HA38 +ENSG00000172667 ZMAT3 testis Leydig cells Medium Enhanced Q9HA38 +ENSG00000172725 CORO1B epididymis glandular cells Medium Enhanced Q9BR76 +ENSG00000172725 CORO1B prostate glandular cells Medium Enhanced Q9BR76 +ENSG00000172725 CORO1B seminal vesicle glandular cells Medium Enhanced Q9BR76 +ENSG00000172725 CORO1B testis cells in seminiferous ducts Low Enhanced Q9BR76 +ENSG00000172725 CORO1B testis Leydig cells Medium Enhanced Q9BR76 +ENSG00000172780 RAB43 testis cells in seminiferous ducts Medium Enhanced Q86YS6 +ENSG00000172780 RAB43 testis Leydig cells Low Enhanced Q86YS6 +ENSG00000172819 RARG epididymis glandular cells High Supported P13631 +ENSG00000172819 RARG prostate glandular cells High Supported P13631 +ENSG00000172819 RARG seminal vesicle glandular cells Medium Supported P13631 +ENSG00000172819 RARG testis cells in seminiferous ducts Medium Supported P13631 +ENSG00000172819 RARG testis Leydig cells Medium Supported P13631 +ENSG00000172831 CES2 epididymis glandular cells Low Enhanced O00748 +ENSG00000172831 CES2 testis cells in seminiferous ducts Medium Enhanced O00748 +ENSG00000172831 CES2 testis Leydig cells Low Enhanced O00748 +ENSG00000172845 SP3 prostate glandular cells Medium Supported Q02447 +ENSG00000172845 SP3 seminal vesicle glandular cells Medium Supported Q02447 +ENSG00000172845 SP3 testis cells in seminiferous ducts Low Supported Q02447 +ENSG00000172915 NBEA epididymis glandular cells Medium Enhanced Q8NFP9 +ENSG00000172915 NBEA prostate glandular cells Medium Enhanced Q8NFP9 +ENSG00000172915 NBEA seminal vesicle glandular cells Medium Enhanced Q8NFP9 +ENSG00000172915 NBEA testis cells in seminiferous ducts Medium Enhanced Q8NFP9 +ENSG00000172915 NBEA testis Leydig cells Medium Enhanced Q8NFP9 +ENSG00000172939 OXSR1 epididymis glandular cells High Enhanced O95747 +ENSG00000172939 OXSR1 prostate glandular cells Medium Enhanced O95747 +ENSG00000172939 OXSR1 seminal vesicle glandular cells Medium Enhanced O95747 +ENSG00000172939 OXSR1 testis cells in seminiferous ducts High Enhanced O95747 +ENSG00000172939 OXSR1 testis Leydig cells Medium Enhanced O95747 +ENSG00000173013 CCDC96 testis elongated or late spermatids High Enhanced Q2M329 +ENSG00000173013 CCDC96 testis Leydig cells High Enhanced Q2M329 +ENSG00000173013 CCDC96 testis pachytene spermatocytes High Enhanced Q2M329 +ENSG00000173013 CCDC96 testis peritubular cells Low Enhanced Q2M329 +ENSG00000173013 CCDC96 testis preleptotene spermatocytes Low Enhanced Q2M329 +ENSG00000173013 CCDC96 testis round or early spermatids High Enhanced Q2M329 +ENSG00000173013 CCDC96 testis spermatogonia Low Enhanced Q2M329 +ENSG00000173039 RELA epididymis glandular cells High Supported Q04206 +ENSG00000173039 RELA prostate glandular cells Medium Supported Q04206 +ENSG00000173039 RELA seminal vesicle glandular cells Low Supported Q04206 +ENSG00000173039 RELA testis cells in seminiferous ducts Medium Supported Q04206 +ENSG00000173039 RELA testis Leydig cells Medium Supported Q04206 +ENSG00000173120 KDM2A epididymis glandular cells High Supported Q9Y2K7 +ENSG00000173120 KDM2A prostate glandular cells Medium Supported Q9Y2K7 +ENSG00000173120 KDM2A seminal vesicle glandular cells Medium Supported Q9Y2K7 +ENSG00000173120 KDM2A testis cells in seminiferous ducts High Supported Q9Y2K7 +ENSG00000173120 KDM2A testis Leydig cells High Supported Q9Y2K7 +ENSG00000173141 MRPL57 epididymis glandular cells Medium Enhanced Q9BQC6 +ENSG00000173141 MRPL57 prostate glandular cells Low Enhanced Q9BQC6 +ENSG00000173141 MRPL57 seminal vesicle glandular cells Medium Enhanced Q9BQC6 +ENSG00000173141 MRPL57 testis cells in seminiferous ducts Medium Enhanced Q9BQC6 +ENSG00000173141 MRPL57 testis Leydig cells Medium Enhanced Q9BQC6 +ENSG00000173193 PARP14 epididymis glandular cells Medium Supported Q460N5 +ENSG00000173193 PARP14 prostate glandular cells Medium Supported Q460N5 +ENSG00000173193 PARP14 seminal vesicle glandular cells Medium Supported Q460N5 +ENSG00000173193 PARP14 testis cells in seminiferous ducts Medium Supported Q460N5 +ENSG00000173193 PARP14 testis Leydig cells Medium Supported Q460N5 +ENSG00000173230 GOLGB1 epididymis glandular cells High Enhanced Q14789 +ENSG00000173230 GOLGB1 prostate glandular cells High Enhanced Q14789 +ENSG00000173230 GOLGB1 seminal vesicle glandular cells High Enhanced Q14789 +ENSG00000173230 GOLGB1 testis cells in seminiferous ducts High Enhanced Q14789 +ENSG00000173230 GOLGB1 testis Leydig cells High Enhanced Q14789 +ENSG00000173262 SLC2A14 testis cells in seminiferous ducts High Supported Q8TDB8 +ENSG00000173262 SLC2A14 testis Leydig cells Low Supported Q8TDB8 +ENSG00000173267 SNCG epididymis glandular cells Medium Enhanced O76070 +ENSG00000173276 ZBTB21 epididymis glandular cells Medium Enhanced Q9ULJ3 +ENSG00000173276 ZBTB21 prostate glandular cells Medium Enhanced Q9ULJ3 +ENSG00000173276 ZBTB21 testis cells in seminiferous ducts Medium Enhanced Q9ULJ3 +ENSG00000173276 ZBTB21 testis Leydig cells Low Enhanced Q9ULJ3 +ENSG00000173401 GLIPR1L1 testis elongated or late spermatids High Enhanced Q6UWM5 +ENSG00000173401 GLIPR1L1 testis Leydig cells Low Enhanced Q6UWM5 +ENSG00000173401 GLIPR1L1 testis pachytene spermatocytes Medium Enhanced Q6UWM5 +ENSG00000173401 GLIPR1L1 testis preleptotene spermatocytes Low Enhanced Q6UWM5 +ENSG00000173401 GLIPR1L1 testis round or early spermatids High Enhanced Q6UWM5 +ENSG00000173402 DAG1 epididymis glandular cells Low Enhanced Q14118 +ENSG00000173402 DAG1 prostate glandular cells Low Enhanced Q14118 +ENSG00000173402 DAG1 testis Leydig cells Low Enhanced Q14118 +ENSG00000173436 MINOS1 epididymis glandular cells Low Enhanced Q5TGZ0 +ENSG00000173436 MINOS1 prostate glandular cells Low Enhanced Q5TGZ0 +ENSG00000173436 MINOS1 seminal vesicle glandular cells High Enhanced Q5TGZ0 +ENSG00000173436 MINOS1 testis cells in seminiferous ducts High Enhanced Q5TGZ0 +ENSG00000173436 MINOS1 testis Leydig cells Medium Enhanced Q5TGZ0 +ENSG00000173473 SMARCC1 epididymis glandular cells Medium Enhanced Q92922 +ENSG00000173473 SMARCC1 prostate glandular cells Medium Enhanced Q92922 +ENSG00000173473 SMARCC1 seminal vesicle glandular cells Low Enhanced Q92922 +ENSG00000173473 SMARCC1 testis cells in seminiferous ducts High Enhanced Q92922 +ENSG00000173482 PTPRM epididymis glandular cells Medium Supported P28827 +ENSG00000173482 PTPRM prostate glandular cells Low Supported P28827 +ENSG00000173482 PTPRM seminal vesicle glandular cells Medium Supported P28827 +ENSG00000173482 PTPRM testis cells in seminiferous ducts Medium Supported P28827 +ENSG00000173482 PTPRM testis Leydig cells Low Supported P28827 +ENSG00000173486 FKBP2 epididymis glandular cells High Enhanced P26885 +ENSG00000173486 FKBP2 seminal vesicle glandular cells High Enhanced P26885 +ENSG00000173542 MOB1B epididymis glandular cells Medium Supported Q7L9L4 +ENSG00000173542 MOB1B prostate glandular cells Medium Supported Q7L9L4 +ENSG00000173542 MOB1B seminal vesicle glandular cells Medium Supported Q7L9L4 +ENSG00000173542 MOB1B testis cells in seminiferous ducts Medium Supported Q7L9L4 +ENSG00000173542 MOB1B testis Leydig cells Medium Supported Q7L9L4 +ENSG00000173557 C2orf70 testis elongated or late spermatids Medium Enhanced A6NJV1 +ENSG00000173557 C2orf70 testis pachytene spermatocytes High Enhanced A6NJV1 +ENSG00000173557 C2orf70 testis preleptotene spermatocytes High Enhanced A6NJV1 +ENSG00000173557 C2orf70 testis round or early spermatids High Enhanced A6NJV1 +ENSG00000173557 C2orf70 testis spermatogonia High Enhanced A6NJV1 +ENSG00000173575 CHD2 epididymis glandular cells High Enhanced O14647 +ENSG00000173575 CHD2 prostate glandular cells Medium Enhanced O14647 +ENSG00000173575 CHD2 seminal vesicle glandular cells High Enhanced O14647 +ENSG00000173575 CHD2 testis cells in seminiferous ducts High Enhanced O14647 +ENSG00000173575 CHD2 testis Leydig cells Medium Enhanced O14647 +ENSG00000173660 UQCRH epididymis glandular cells Low Supported P07919 +ENSG00000173660 UQCRH prostate glandular cells Low Supported P07919 +ENSG00000173660 UQCRH seminal vesicle glandular cells High Supported P07919 +ENSG00000173660 UQCRH testis cells in seminiferous ducts Medium Supported P07919 +ENSG00000173660 UQCRH testis Leydig cells Medium Supported P07919 +ENSG00000173678 SPDYE2B testis elongated or late spermatids High Supported A6NHP3 +ENSG00000173678 SPDYE2B testis round or early spermatids Medium Supported A6NHP3 +ENSG00000173692 PSMD1 epididymis glandular cells Medium Enhanced Q99460 +ENSG00000173692 PSMD1 prostate glandular cells Medium Enhanced Q99460 +ENSG00000173692 PSMD1 seminal vesicle glandular cells Medium Enhanced Q99460 +ENSG00000173692 PSMD1 testis cells in seminiferous ducts High Enhanced Q99460 +ENSG00000173692 PSMD1 testis Leydig cells High Enhanced Q99460 +ENSG00000173698 ADGRG2 epididymis glandular cells Medium Enhanced Q8IZP9 +ENSG00000173699 SPATA3 testis elongated or late spermatids High Enhanced Q8NHX4 +ENSG00000173699 SPATA3 testis Leydig cells Low Enhanced Q8NHX4 +ENSG00000173726 TOMM20 epididymis glandular cells High Supported Q15388 +ENSG00000173726 TOMM20 prostate glandular cells High Supported Q15388 +ENSG00000173726 TOMM20 seminal vesicle glandular cells High Supported Q15388 +ENSG00000173726 TOMM20 testis cells in seminiferous ducts High Supported Q15388 +ENSG00000173726 TOMM20 testis Leydig cells High Supported Q15388 +ENSG00000173801 JUP epididymis glandular cells High Supported P14923 +ENSG00000173801 JUP prostate glandular cells High Supported P14923 +ENSG00000173801 JUP seminal vesicle glandular cells High Supported P14923 +ENSG00000173801 JUP testis cells in seminiferous ducts Medium Supported P14923 +ENSG00000173801 JUP testis Leydig cells Medium Supported P14923 +ENSG00000173838 MARCH10 testis pachytene spermatocytes High Enhanced Q8NA82 +ENSG00000173838 MARCH10 testis preleptotene spermatocytes Low Enhanced Q8NA82 +ENSG00000173838 MARCH10 testis round or early spermatids High Enhanced Q8NA82 +ENSG00000173838 MARCH10 testis spermatogonia Low Enhanced Q8NA82 +ENSG00000173846 PLK3 epididymis glandular cells Medium Enhanced Q9H4B4 +ENSG00000173846 PLK3 prostate glandular cells Low Enhanced Q9H4B4 +ENSG00000173846 PLK3 seminal vesicle glandular cells Medium Enhanced Q9H4B4 +ENSG00000173846 PLK3 testis cells in seminiferous ducts Low Enhanced Q9H4B4 +ENSG00000173846 PLK3 testis Leydig cells High Enhanced Q9H4B4 +ENSG00000173898 SPTBN2 epididymis glandular cells Low Enhanced O15020 +ENSG00000173898 SPTBN2 prostate glandular cells High Enhanced O15020 +ENSG00000173898 SPTBN2 seminal vesicle glandular cells Medium Enhanced O15020 +ENSG00000173898 SPTBN2 testis cells in seminiferous ducts Low Enhanced O15020 +ENSG00000173905 GOLIM4 epididymis glandular cells Medium Enhanced O00461 +ENSG00000173905 GOLIM4 prostate glandular cells Medium Enhanced O00461 +ENSG00000173905 GOLIM4 seminal vesicle glandular cells Low Enhanced O00461 +ENSG00000173905 GOLIM4 testis cells in seminiferous ducts Low Enhanced O00461 +ENSG00000173905 GOLIM4 testis Leydig cells Medium Enhanced O00461 +ENSG00000173960 UBXN2A epididymis glandular cells Medium Supported P68543 +ENSG00000173960 UBXN2A prostate glandular cells Medium Supported P68543 +ENSG00000173960 UBXN2A seminal vesicle glandular cells Medium Supported P68543 +ENSG00000173960 UBXN2A testis cells in seminiferous ducts Medium Supported P68543 +ENSG00000173960 UBXN2A testis Leydig cells High Supported P68543 +ENSG00000174007 CEP19 epididymis glandular cells Low Enhanced Q96LK0 +ENSG00000174007 CEP19 testis elongated or late spermatids High Enhanced Q96LK0 +ENSG00000174007 CEP19 testis Leydig cells Low Enhanced Q96LK0 +ENSG00000174007 CEP19 testis round or early spermatids Low Enhanced Q96LK0 +ENSG00000174015 SPERT testis elongated or late spermatids High Enhanced Q8NA61 +ENSG00000174015 SPERT testis round or early spermatids Medium Enhanced Q8NA61 +ENSG00000174137 FAM53A epididymis glandular cells Low Enhanced Q6NSI3 +ENSG00000174137 FAM53A prostate glandular cells Low Enhanced Q6NSI3 +ENSG00000174137 FAM53A seminal vesicle glandular cells Low Enhanced Q6NSI3 +ENSG00000174137 FAM53A testis elongated or late spermatids Low Enhanced Q6NSI3 +ENSG00000174137 FAM53A testis Leydig cells Low Enhanced Q6NSI3 +ENSG00000174137 FAM53A testis pachytene spermatocytes High Enhanced Q6NSI3 +ENSG00000174137 FAM53A testis preleptotene spermatocytes High Enhanced Q6NSI3 +ENSG00000174137 FAM53A testis round or early spermatids Low Enhanced Q6NSI3 +ENSG00000174137 FAM53A testis sertoli cells Medium Enhanced Q6NSI3 +ENSG00000174137 FAM53A testis spermatogonia High Enhanced Q6NSI3 +ENSG00000174231 PRPF8 epididymis glandular cells Medium Supported I3L1T8 +ENSG00000174231 PRPF8 seminal vesicle glandular cells Medium Supported I3L1T8 +ENSG00000174231 PRPF8 testis cells in seminiferous ducts High Supported I3L1T8 +ENSG00000174231 PRPF8 testis Leydig cells Medium Supported I3L1T8 +ENSG00000174282 ZBTB4 epididymis glandular cells Medium Supported NA +ENSG00000174282 ZBTB4 prostate glandular cells Medium Supported NA +ENSG00000174282 ZBTB4 seminal vesicle glandular cells Medium Supported NA +ENSG00000174282 ZBTB4 testis cells in seminiferous ducts Low Supported NA +ENSG00000174282 ZBTB4 testis Leydig cells Medium Supported NA +ENSG00000174405 LIG4 epididymis glandular cells Medium Supported P49917 +ENSG00000174405 LIG4 prostate glandular cells Medium Supported P49917 +ENSG00000174405 LIG4 seminal vesicle glandular cells Medium Supported P49917 +ENSG00000174405 LIG4 testis cells in seminiferous ducts Medium Supported P49917 +ENSG00000174405 LIG4 testis Leydig cells Medium Supported P49917 +ENSG00000174437 ATP2A2 epididymis glandular cells Low Enhanced P16615 +ENSG00000174437 ATP2A2 testis cells in seminiferous ducts Low Enhanced P16615 +ENSG00000174502 SLC26A9 prostate glandular cells Medium Enhanced Q7LBE3 +ENSG00000174502 SLC26A9 testis Leydig cells Low Enhanced Q7LBE3 +ENSG00000174640 SLCO2A1 seminal vesicle glandular cells High Enhanced Q92959 +ENSG00000174640 SLCO2A1 testis cells in seminiferous ducts Low Enhanced Q92959 +ENSG00000174640 SLCO2A1 testis Leydig cells Low Enhanced Q92959 +ENSG00000174891 RSRC1 epididymis glandular cells Medium Enhanced Q96IZ7 +ENSG00000174891 RSRC1 prostate glandular cells Medium Enhanced Q96IZ7 +ENSG00000174891 RSRC1 seminal vesicle glandular cells Medium Enhanced Q96IZ7 +ENSG00000174891 RSRC1 testis cells in seminiferous ducts Medium Enhanced Q96IZ7 +ENSG00000174891 RSRC1 testis Leydig cells Medium Enhanced Q96IZ7 +ENSG00000174898 CATSPERD testis elongated or late spermatids High Supported Q86XM0 +ENSG00000174898 CATSPERD testis Leydig cells Low Supported Q86XM0 +ENSG00000174898 CATSPERD testis preleptotene spermatocytes Low Supported Q86XM0 +ENSG00000174898 CATSPERD testis round or early spermatids High Supported Q86XM0 +ENSG00000174898 CATSPERD testis spermatogonia Low Supported Q86XM0 +ENSG00000174938 SEZ6L2 epididymis glandular cells Medium Enhanced Q6UXD5 +ENSG00000174938 SEZ6L2 prostate glandular cells Low Enhanced Q6UXD5 +ENSG00000174938 SEZ6L2 testis cells in seminiferous ducts Low Enhanced Q6UXD5 +ENSG00000174938 SEZ6L2 testis Leydig cells Low Enhanced Q6UXD5 +ENSG00000174943 KCTD13 epididymis glandular cells Medium Enhanced Q8WZ19 +ENSG00000174943 KCTD13 prostate glandular cells Medium Enhanced Q8WZ19 +ENSG00000174943 KCTD13 seminal vesicle glandular cells Medium Enhanced Q8WZ19 +ENSG00000174943 KCTD13 testis cells in seminiferous ducts Low Enhanced Q8WZ19 +ENSG00000174943 KCTD13 testis Leydig cells High Enhanced Q8WZ19 +ENSG00000174950 CD164L2 seminal vesicle glandular cells Low Enhanced Q6UWJ8 +ENSG00000174989 FBXW8 epididymis glandular cells Medium Enhanced Q8N3Y1 +ENSG00000174989 FBXW8 prostate glandular cells Medium Enhanced Q8N3Y1 +ENSG00000174989 FBXW8 seminal vesicle glandular cells Medium Enhanced Q8N3Y1 +ENSG00000174989 FBXW8 testis cells in seminiferous ducts Medium Enhanced Q8N3Y1 +ENSG00000174989 FBXW8 testis Leydig cells Medium Enhanced Q8N3Y1 +ENSG00000174996 KLC2 epididymis glandular cells Medium Enhanced Q9H0B6 +ENSG00000174996 KLC2 prostate glandular cells Medium Enhanced Q9H0B6 +ENSG00000174996 KLC2 seminal vesicle glandular cells Medium Enhanced Q9H0B6 +ENSG00000174996 KLC2 testis cells in seminiferous ducts High Enhanced Q9H0B6 +ENSG00000174996 KLC2 testis Leydig cells Medium Enhanced Q9H0B6 +ENSG00000175110 MRPS22 epididymis glandular cells Medium Enhanced P82650 +ENSG00000175110 MRPS22 prostate glandular cells Medium Enhanced P82650 +ENSG00000175110 MRPS22 seminal vesicle glandular cells Medium Enhanced P82650 +ENSG00000175110 MRPS22 testis cells in seminiferous ducts Medium Enhanced P82650 +ENSG00000175110 MRPS22 testis Leydig cells High Enhanced P82650 +ENSG00000175198 PCCA epididymis glandular cells Medium Enhanced P05165 +ENSG00000175198 PCCA prostate glandular cells High Enhanced P05165 +ENSG00000175198 PCCA seminal vesicle glandular cells High Enhanced P05165 +ENSG00000175198 PCCA testis cells in seminiferous ducts Medium Enhanced P05165 +ENSG00000175198 PCCA testis Leydig cells High Enhanced P05165 +ENSG00000175203 DCTN2 epididymis glandular cells Medium Enhanced Q13561 +ENSG00000175203 DCTN2 prostate glandular cells High Enhanced Q13561 +ENSG00000175203 DCTN2 seminal vesicle glandular cells High Enhanced Q13561 +ENSG00000175203 DCTN2 testis cells in seminiferous ducts High Enhanced Q13561 +ENSG00000175203 DCTN2 testis Leydig cells Medium Enhanced Q13561 +ENSG00000175216 CKAP5 epididymis glandular cells Medium Enhanced Q14008 +ENSG00000175216 CKAP5 prostate glandular cells Medium Enhanced Q14008 +ENSG00000175216 CKAP5 seminal vesicle glandular cells Medium Enhanced Q14008 +ENSG00000175216 CKAP5 testis cells in seminiferous ducts High Enhanced Q14008 +ENSG00000175216 CKAP5 testis Leydig cells High Enhanced Q14008 +ENSG00000175305 CCNE2 seminal vesicle glandular cells Low Enhanced O96020 +ENSG00000175305 CCNE2 testis cells in seminiferous ducts Medium Enhanced O96020 +ENSG00000175305 CCNE2 testis Leydig cells Low Enhanced O96020 +ENSG00000175334 BANF1 epididymis glandular cells High Enhanced O75531 +ENSG00000175334 BANF1 prostate glandular cells Low Enhanced O75531 +ENSG00000175334 BANF1 seminal vesicle glandular cells Medium Enhanced O75531 +ENSG00000175334 BANF1 testis cells in seminiferous ducts High Enhanced O75531 +ENSG00000175334 BANF1 testis Leydig cells Low Enhanced O75531 +ENSG00000175344 CHRNA7 epididymis glandular cells Medium Enhanced P36544 +ENSG00000175344 CHRNA7 prostate glandular cells Low Enhanced P36544 +ENSG00000175344 CHRNA7 seminal vesicle glandular cells Medium Enhanced P36544 +ENSG00000175344 CHRNA7 testis cells in seminiferous ducts Medium Enhanced P36544 +ENSG00000175344 CHRNA7 testis Leydig cells Medium Enhanced P36544 +ENSG00000175354 PTPN2 epididymis glandular cells Medium Enhanced P17706 +ENSG00000175354 PTPN2 prostate glandular cells Medium Enhanced P17706 +ENSG00000175354 PTPN2 seminal vesicle glandular cells Medium Enhanced P17706 +ENSG00000175354 PTPN2 testis cells in seminiferous ducts Medium Enhanced P17706 +ENSG00000175354 PTPN2 testis Leydig cells Medium Enhanced P17706 +ENSG00000175467 SART1 epididymis glandular cells Medium Supported O43290 +ENSG00000175467 SART1 testis cells in seminiferous ducts Medium Supported O43290 +ENSG00000175467 SART1 testis Leydig cells Low Supported O43290 +ENSG00000175520 UBQLN3 testis elongated or late spermatids High Enhanced Q9H347 +ENSG00000175520 UBQLN3 testis pachytene spermatocytes Low Enhanced Q9H347 +ENSG00000175520 UBQLN3 testis preleptotene spermatocytes Low Enhanced Q9H347 +ENSG00000175520 UBQLN3 testis round or early spermatids High Enhanced Q9H347 +ENSG00000175600 SUGCT epididymis glandular cells Medium Enhanced Q9HAC7 +ENSG00000175600 SUGCT prostate glandular cells Medium Enhanced Q9HAC7 +ENSG00000175600 SUGCT seminal vesicle glandular cells Low Enhanced Q9HAC7 +ENSG00000175600 SUGCT testis cells in seminiferous ducts Medium Enhanced Q9HAC7 +ENSG00000175600 SUGCT testis Leydig cells Medium Enhanced Q9HAC7 +ENSG00000175646 PRM1 testis elongated or late spermatids High Enhanced P04553 +ENSG00000175662 TOM1L2 epididymis glandular cells Medium Enhanced Q6ZVM7 +ENSG00000175662 TOM1L2 prostate glandular cells High Enhanced Q6ZVM7 +ENSG00000175662 TOM1L2 seminal vesicle glandular cells Low Enhanced Q6ZVM7 +ENSG00000175662 TOM1L2 testis cells in seminiferous ducts Medium Enhanced Q6ZVM7 +ENSG00000175662 TOM1L2 testis Leydig cells Medium Enhanced Q6ZVM7 +ENSG00000175711 B3GNTL1 epididymis glandular cells Low Supported NA +ENSG00000175711 B3GNTL1 prostate glandular cells Low Supported NA +ENSG00000175711 B3GNTL1 seminal vesicle glandular cells Medium Supported NA +ENSG00000175711 B3GNTL1 testis cells in seminiferous ducts Low Supported NA +ENSG00000175711 B3GNTL1 testis Leydig cells Medium Supported NA +ENSG00000175718 RBMXL3 testis pachytene spermatocytes High Supported Q8N7X1 +ENSG00000175718 RBMXL3 testis preleptotene spermatocytes High Supported Q8N7X1 +ENSG00000175718 RBMXL3 testis round or early spermatids High Supported Q8N7X1 +ENSG00000175718 RBMXL3 testis spermatogonia High Supported Q8N7X1 +ENSG00000175792 RUVBL1 epididymis glandular cells Low Enhanced Q9Y265 +ENSG00000175792 RUVBL1 prostate glandular cells Low Enhanced Q9Y265 +ENSG00000175792 RUVBL1 seminal vesicle glandular cells Low Enhanced Q9Y265 +ENSG00000175792 RUVBL1 testis cells in seminiferous ducts High Enhanced Q9Y265 +ENSG00000175792 RUVBL1 testis Leydig cells Low Enhanced Q9Y265 +ENSG00000175793 SFN prostate glandular cells Low Enhanced P31947 +ENSG00000175793 SFN seminal vesicle glandular cells Low Enhanced P31947 +ENSG00000175866 BAIAP2 epididymis glandular cells High Enhanced Q9UQB8 +ENSG00000175866 BAIAP2 prostate glandular cells High Enhanced Q9UQB8 +ENSG00000175866 BAIAP2 seminal vesicle glandular cells Medium Enhanced Q9UQB8 +ENSG00000175866 BAIAP2 testis cells in seminiferous ducts Medium Enhanced Q9UQB8 +ENSG00000175866 BAIAP2 testis Leydig cells Medium Enhanced Q9UQB8 +ENSG00000175899 A2M epididymis glandular cells Low Supported P01023 +ENSG00000175899 A2M prostate glandular cells Low Supported P01023 +ENSG00000175899 A2M testis Leydig cells Low Supported P01023 +ENSG00000175928 LRRN1 testis cells in seminiferous ducts Medium Enhanced Q6UXK5 +ENSG00000175928 LRRN1 testis Leydig cells Medium Enhanced Q6UXK5 +ENSG00000176102 CSTF3 epididymis glandular cells High Enhanced Q12996 +ENSG00000176102 CSTF3 prostate glandular cells Medium Enhanced Q12996 +ENSG00000176102 CSTF3 seminal vesicle glandular cells Medium Enhanced Q12996 +ENSG00000176102 CSTF3 testis cells in seminiferous ducts High Enhanced Q12996 +ENSG00000176102 CSTF3 testis Leydig cells High Enhanced Q12996 +ENSG00000176160 HSF5 testis elongated or late spermatids Medium Enhanced Q4G112 +ENSG00000176160 HSF5 testis Leydig cells Medium Enhanced Q4G112 +ENSG00000176160 HSF5 testis pachytene spermatocytes High Enhanced Q4G112 +ENSG00000176160 HSF5 testis preleptotene spermatocytes Low Enhanced Q4G112 +ENSG00000176160 HSF5 testis round or early spermatids High Enhanced Q4G112 +ENSG00000176171 BNIP3 epididymis glandular cells Medium Supported Q12983 +ENSG00000176171 BNIP3 prostate glandular cells High Supported Q12983 +ENSG00000176171 BNIP3 seminal vesicle glandular cells Medium Supported Q12983 +ENSG00000176171 BNIP3 testis cells in seminiferous ducts Medium Supported Q12983 +ENSG00000176171 BNIP3 testis Leydig cells Medium Supported Q12983 +ENSG00000176248 ANAPC2 epididymis glandular cells Medium Enhanced Q9UJX6 +ENSG00000176248 ANAPC2 prostate glandular cells Medium Enhanced Q9UJX6 +ENSG00000176248 ANAPC2 seminal vesicle glandular cells Medium Enhanced Q9UJX6 +ENSG00000176248 ANAPC2 testis cells in seminiferous ducts High Enhanced Q9UJX6 +ENSG00000176256 HMGB4 testis elongated or late spermatids High Enhanced Q8WW32 +ENSG00000176256 HMGB4 testis Leydig cells Low Enhanced Q8WW32 +ENSG00000176256 HMGB4 testis round or early spermatids High Enhanced Q8WW32 +ENSG00000176340 COX8A epididymis glandular cells Medium Supported P10176 +ENSG00000176340 COX8A prostate glandular cells Medium Supported P10176 +ENSG00000176340 COX8A seminal vesicle glandular cells Medium Supported P10176 +ENSG00000176340 COX8A testis cells in seminiferous ducts Medium Supported P10176 +ENSG00000176340 COX8A testis Leydig cells Low Supported P10176 +ENSG00000176371 ZSCAN2 epididymis glandular cells High Supported Q7Z7L9 +ENSG00000176371 ZSCAN2 prostate glandular cells High Supported Q7Z7L9 +ENSG00000176371 ZSCAN2 seminal vesicle glandular cells High Supported Q7Z7L9 +ENSG00000176371 ZSCAN2 testis cells in seminiferous ducts High Supported Q7Z7L9 +ENSG00000176371 ZSCAN2 testis Leydig cells High Supported Q7Z7L9 +ENSG00000176387 HSD11B2 testis Leydig cells Low Enhanced P80365 +ENSG00000176390 CRLF3 testis cells in seminiferous ducts High Enhanced Q8IUI8 +ENSG00000176390 CRLF3 testis Leydig cells Low Enhanced Q8IUI8 +ENSG00000176407 KCMF1 epididymis glandular cells Medium Enhanced Q9P0J7 +ENSG00000176407 KCMF1 prostate glandular cells Medium Enhanced Q9P0J7 +ENSG00000176407 KCMF1 seminal vesicle glandular cells Medium Enhanced Q9P0J7 +ENSG00000176407 KCMF1 testis cells in seminiferous ducts Medium Enhanced Q9P0J7 +ENSG00000176407 KCMF1 testis Leydig cells Medium Enhanced Q9P0J7 +ENSG00000176476 SGF29 seminal vesicle glandular cells Low Enhanced Q96ES7 +ENSG00000176476 SGF29 testis cells in seminiferous ducts High Enhanced Q96ES7 +ENSG00000176476 SGF29 testis Leydig cells Low Enhanced Q96ES7 +ENSG00000176532 PRR15 epididymis glandular cells Medium Enhanced Q8IV56 +ENSG00000176619 LMNB2 epididymis glandular cells High Enhanced Q03252 +ENSG00000176619 LMNB2 prostate glandular cells Medium Enhanced Q03252 +ENSG00000176619 LMNB2 seminal vesicle glandular cells Medium Enhanced Q03252 +ENSG00000176619 LMNB2 testis cells in seminiferous ducts Low Enhanced Q03252 +ENSG00000176619 LMNB2 testis Leydig cells Medium Enhanced Q03252 +ENSG00000176635 HORMAD2 testis Leydig cells High Enhanced Q8N7B1 +ENSG00000176635 HORMAD2 testis pachytene spermatocytes Medium Enhanced Q8N7B1 +ENSG00000176681 LRRC37A testis elongated or late spermatids High Supported A6NMS7 +ENSG00000176681 LRRC37A testis pachytene spermatocytes Low Supported A6NMS7 +ENSG00000176681 LRRC37A testis preleptotene spermatocytes Low Supported A6NMS7 +ENSG00000176681 LRRC37A testis round or early spermatids High Supported A6NMS7 +ENSG00000176697 BDNF testis Leydig cells Low Enhanced P23560 +ENSG00000176774 MAGEB18 testis cells in seminiferous ducts High Enhanced Q96M61 +ENSG00000176782 DEFB104A epididymis glandular cells Low Supported NA +ENSG00000176788 BASP1 epididymis glandular cells High Enhanced P80723 +ENSG00000176788 BASP1 prostate glandular cells High Enhanced P80723 +ENSG00000176788 BASP1 seminal vesicle glandular cells Medium Enhanced P80723 +ENSG00000176809 LRRC37A3 testis elongated or late spermatids High Supported O60309 +ENSG00000176809 LRRC37A3 testis pachytene spermatocytes Low Supported O60309 +ENSG00000176809 LRRC37A3 testis preleptotene spermatocytes Low Supported O60309 +ENSG00000176809 LRRC37A3 testis round or early spermatids High Supported O60309 +ENSG00000176890 TYMS epididymis glandular cells Medium Enhanced P04818 +ENSG00000176890 TYMS prostate glandular cells Low Enhanced P04818 +ENSG00000176890 TYMS seminal vesicle glandular cells Medium Enhanced P04818 +ENSG00000176890 TYMS testis cells in seminiferous ducts Medium Enhanced P04818 +ENSG00000176890 TYMS testis Leydig cells Medium Enhanced P04818 +ENSG00000176903 PNMA1 epididymis glandular cells Low Enhanced Q8ND90 +ENSG00000176903 PNMA1 prostate glandular cells Low Enhanced Q8ND90 +ENSG00000176903 PNMA1 seminal vesicle glandular cells Low Enhanced Q8ND90 +ENSG00000176903 PNMA1 testis cells in seminiferous ducts Medium Enhanced Q8ND90 +ENSG00000176903 PNMA1 testis Leydig cells Medium Enhanced Q8ND90 +ENSG00000176978 DPP7 epididymis glandular cells High Supported Q9UHL4 +ENSG00000176978 DPP7 prostate glandular cells Medium Supported Q9UHL4 +ENSG00000176978 DPP7 seminal vesicle glandular cells Medium Supported Q9UHL4 +ENSG00000176978 DPP7 testis cells in seminiferous ducts Medium Supported Q9UHL4 +ENSG00000176978 DPP7 testis Leydig cells High Supported Q9UHL4 +ENSG00000176986 SEC24C epididymis glandular cells Medium Supported P53992 +ENSG00000176986 SEC24C prostate glandular cells Medium Supported P53992 +ENSG00000176986 SEC24C seminal vesicle glandular cells Medium Supported P53992 +ENSG00000176986 SEC24C testis cells in seminiferous ducts Medium Supported P53992 +ENSG00000176986 SEC24C testis Leydig cells Medium Supported P53992 +ENSG00000176988 FMR1NB testis elongated or late spermatids High Enhanced Q8N0W7 +ENSG00000176988 FMR1NB testis Leydig cells Low Enhanced Q8N0W7 +ENSG00000176988 FMR1NB testis pachytene spermatocytes High Enhanced Q8N0W7 +ENSG00000176988 FMR1NB testis preleptotene spermatocytes High Enhanced Q8N0W7 +ENSG00000176988 FMR1NB testis round or early spermatids High Enhanced Q8N0W7 +ENSG00000176988 FMR1NB testis spermatogonia High Enhanced Q8N0W7 +ENSG00000177023 DEFB104B epididymis glandular cells Low Supported NA +ENSG00000177191 B3GNT8 seminal vesicle glandular cells Medium Enhanced Q7Z7M8 +ENSG00000177191 B3GNT8 testis Leydig cells Low Enhanced Q7Z7M8 +ENSG00000177202 SPACA4 testis elongated or late spermatids High Enhanced Q8TDM5 +ENSG00000177202 SPACA4 testis round or early spermatids High Enhanced Q8TDM5 +ENSG00000177303 CASKIN2 epididymis glandular cells Medium Enhanced Q8WXE0 +ENSG00000177303 CASKIN2 prostate glandular cells Low Enhanced Q8WXE0 +ENSG00000177303 CASKIN2 testis cells in seminiferous ducts Medium Enhanced Q8WXE0 +ENSG00000177303 CASKIN2 testis Leydig cells Medium Enhanced Q8WXE0 +ENSG00000177324 BEND2 testis pachytene spermatocytes High Enhanced Q8NDZ0 +ENSG00000177324 BEND2 testis preleptotene spermatocytes Low Enhanced Q8NDZ0 +ENSG00000177363 LRRN4CL epididymis glandular cells Medium Enhanced Q8ND94 +ENSG00000177363 LRRN4CL prostate glandular cells Medium Enhanced Q8ND94 +ENSG00000177363 LRRN4CL seminal vesicle glandular cells Medium Enhanced Q8ND94 +ENSG00000177363 LRRN4CL testis cells in seminiferous ducts Medium Enhanced Q8ND94 +ENSG00000177363 LRRN4CL testis Leydig cells Medium Enhanced Q8ND94 +ENSG00000177409 SAMD9L epididymis glandular cells Medium Enhanced Q8IVG5 +ENSG00000177409 SAMD9L prostate glandular cells Medium Enhanced Q8IVG5 +ENSG00000177409 SAMD9L seminal vesicle glandular cells Medium Enhanced Q8IVG5 +ENSG00000177409 SAMD9L testis cells in seminiferous ducts Medium Enhanced Q8IVG5 +ENSG00000177409 SAMD9L testis Leydig cells Medium Enhanced Q8IVG5 +ENSG00000177459 ERICH5 testis cells in seminiferous ducts Low Enhanced Q6P6B1 +ENSG00000177465 ACOT4 epididymis glandular cells Low Enhanced Q8N9L9 +ENSG00000177465 ACOT4 prostate glandular cells Low Enhanced Q8N9L9 +ENSG00000177465 ACOT4 seminal vesicle glandular cells High Enhanced Q8N9L9 +ENSG00000177465 ACOT4 testis cells in seminiferous ducts Low Enhanced Q8N9L9 +ENSG00000177465 ACOT4 testis Leydig cells Low Enhanced Q8N9L9 +ENSG00000177469 PTRF testis Leydig cells Medium Supported Q6NZI2 +ENSG00000177483 RBM44 testis elongated or late spermatids Low Enhanced Q6ZP01 +ENSG00000177483 RBM44 testis pachytene spermatocytes High Enhanced Q6ZP01 +ENSG00000177483 RBM44 testis preleptotene spermatocytes Medium Enhanced Q6ZP01 +ENSG00000177483 RBM44 testis round or early spermatids Low Enhanced Q6ZP01 +ENSG00000177504 VCX2 testis pachytene spermatocytes High Enhanced Q9H322 +ENSG00000177504 VCX2 testis preleptotene spermatocytes High Enhanced Q9H322 +ENSG00000177504 VCX2 testis round or early spermatids High Enhanced Q9H322 +ENSG00000177504 VCX2 testis spermatogonia High Enhanced Q9H322 +ENSG00000177565 TBL1XR1 epididymis glandular cells High Supported Q9BZK7 +ENSG00000177565 TBL1XR1 prostate glandular cells High Supported Q9BZK7 +ENSG00000177565 TBL1XR1 seminal vesicle glandular cells High Supported Q9BZK7 +ENSG00000177565 TBL1XR1 testis cells in seminiferous ducts High Supported Q9BZK7 +ENSG00000177565 TBL1XR1 testis Leydig cells High Supported Q9BZK7 +ENSG00000177595 PIDD1 epididymis glandular cells Medium Supported Q9HB75 +ENSG00000177595 PIDD1 prostate glandular cells High Supported Q9HB75 +ENSG00000177595 PIDD1 seminal vesicle glandular cells Medium Supported Q9HB75 +ENSG00000177595 PIDD1 testis cells in seminiferous ducts High Supported Q9HB75 +ENSG00000177595 PIDD1 testis Leydig cells Medium Supported Q9HB75 +ENSG00000177606 JUN epididymis glandular cells Low Enhanced P05412 +ENSG00000177628 GBA epididymis glandular cells High Supported P04062 +ENSG00000177628 GBA prostate glandular cells High Supported P04062 +ENSG00000177628 GBA seminal vesicle glandular cells High Supported P04062 +ENSG00000177628 GBA testis cells in seminiferous ducts Low Supported P04062 +ENSG00000177628 GBA testis Leydig cells High Supported P04062 +ENSG00000177646 ACAD9 epididymis glandular cells Medium Supported Q9H845 +ENSG00000177646 ACAD9 prostate glandular cells Low Supported Q9H845 +ENSG00000177646 ACAD9 seminal vesicle glandular cells High Supported Q9H845 +ENSG00000177646 ACAD9 testis cells in seminiferous ducts Medium Supported Q9H845 +ENSG00000177646 ACAD9 testis Leydig cells Medium Supported Q9H845 +ENSG00000177663 IL17RA epididymis glandular cells Medium Enhanced Q96F46 +ENSG00000177663 IL17RA prostate glandular cells Low Enhanced Q96F46 +ENSG00000177663 IL17RA seminal vesicle glandular cells Medium Enhanced Q96F46 +ENSG00000177663 IL17RA testis Leydig cells Low Enhanced Q96F46 +ENSG00000177673 TEX44 testis elongated or late spermatids High Enhanced Q53QW1 +ENSG00000177673 TEX44 testis Leydig cells Low Enhanced Q53QW1 +ENSG00000177673 TEX44 testis pachytene spermatocytes Medium Enhanced Q53QW1 +ENSG00000177673 TEX44 testis preleptotene spermatocytes Medium Enhanced Q53QW1 +ENSG00000177673 TEX44 testis round or early spermatids Medium Enhanced Q53QW1 +ENSG00000177697 CD151 epididymis glandular cells Low Supported P48509 +ENSG00000177697 CD151 prostate glandular cells High Supported P48509 +ENSG00000177697 CD151 seminal vesicle glandular cells Medium Supported P48509 +ENSG00000177697 CD151 testis cells in seminiferous ducts Low Supported P48509 +ENSG00000177697 CD151 testis Leydig cells Low Supported P48509 +ENSG00000177733 HNRNPA0 epididymis glandular cells Medium Enhanced Q13151 +ENSG00000177733 HNRNPA0 prostate glandular cells Medium Enhanced Q13151 +ENSG00000177733 HNRNPA0 seminal vesicle glandular cells Medium Enhanced Q13151 +ENSG00000177733 HNRNPA0 testis cells in seminiferous ducts Medium Enhanced Q13151 +ENSG00000177733 HNRNPA0 testis Leydig cells Low Enhanced Q13151 +ENSG00000177889 UBE2N epididymis glandular cells Low Enhanced P61088 +ENSG00000177889 UBE2N prostate glandular cells Low Enhanced P61088 +ENSG00000177889 UBE2N seminal vesicle glandular cells Medium Enhanced P61088 +ENSG00000177889 UBE2N testis cells in seminiferous ducts High Enhanced P61088 +ENSG00000177889 UBE2N testis Leydig cells Medium Enhanced P61088 +ENSG00000177917 ARL6IP6 epididymis glandular cells Low Enhanced Q8N6S5 +ENSG00000177917 ARL6IP6 testis cells in seminiferous ducts Low Enhanced Q8N6S5 +ENSG00000177917 ARL6IP6 testis Leydig cells High Enhanced Q8N6S5 +ENSG00000177938 CAPZA3 testis elongated or late spermatids High Enhanced Q96KX2 +ENSG00000177938 CAPZA3 testis Leydig cells Low Enhanced Q96KX2 +ENSG00000177938 CAPZA3 testis pachytene spermatocytes Medium Enhanced Q96KX2 +ENSG00000177938 CAPZA3 testis preleptotene spermatocytes Medium Enhanced Q96KX2 +ENSG00000177938 CAPZA3 testis round or early spermatids Medium Enhanced Q96KX2 +ENSG00000177938 CAPZA3 testis spermatogonia Low Enhanced Q96KX2 +ENSG00000177947 ODF3 testis cells in seminiferous ducts Medium Enhanced Q96PU9 +ENSG00000177992 SPATA31E1 testis elongated or late spermatids High Enhanced Q6ZUB1 +ENSG00000177992 SPATA31E1 testis pachytene spermatocytes High Enhanced Q6ZUB1 +ENSG00000177992 SPATA31E1 testis round or early spermatids High Enhanced Q6ZUB1 +ENSG00000178021 TSPYL6 testis pachytene spermatocytes High Enhanced Q8N831 +ENSG00000178021 TSPYL6 testis preleptotene spermatocytes High Enhanced Q8N831 +ENSG00000178021 TSPYL6 testis round or early spermatids High Enhanced Q8N831 +ENSG00000178021 TSPYL6 testis spermatogonia High Enhanced Q8N831 +ENSG00000178057 NDUFAF3 epididymis glandular cells Medium Enhanced Q9BU61 +ENSG00000178057 NDUFAF3 prostate glandular cells High Enhanced Q9BU61 +ENSG00000178057 NDUFAF3 seminal vesicle glandular cells Medium Enhanced Q9BU61 +ENSG00000178057 NDUFAF3 testis cells in seminiferous ducts High Enhanced Q9BU61 +ENSG00000178057 NDUFAF3 testis Leydig cells High Enhanced Q9BU61 +ENSG00000178127 NDUFV2 epididymis glandular cells Medium Supported P19404 +ENSG00000178127 NDUFV2 prostate glandular cells Medium Supported P19404 +ENSG00000178127 NDUFV2 seminal vesicle glandular cells High Supported P19404 +ENSG00000178127 NDUFV2 testis cells in seminiferous ducts Low Supported P19404 +ENSG00000178127 NDUFV2 testis Leydig cells Low Supported P19404 +ENSG00000178209 PLEC epididymis glandular cells Medium Enhanced Q15149 +ENSG00000178209 PLEC prostate glandular cells Medium Enhanced Q15149 +ENSG00000178209 PLEC seminal vesicle glandular cells Medium Enhanced Q15149 +ENSG00000178209 PLEC testis cells in seminiferous ducts Medium Enhanced Q15149 +ENSG00000178209 PLEC testis Leydig cells Low Enhanced Q15149 +ENSG00000178287 SPAG11A epididymis glandular cells High Supported Q6PDA7 +ENSG00000178467 P4HTM epididymis glandular cells High Supported Q9NXG6 +ENSG00000178467 P4HTM prostate glandular cells High Supported Q9NXG6 +ENSG00000178467 P4HTM seminal vesicle glandular cells High Supported Q9NXG6 +ENSG00000178467 P4HTM testis cells in seminiferous ducts Medium Supported Q9NXG6 +ENSG00000178467 P4HTM testis Leydig cells High Supported Q9NXG6 +ENSG00000178568 ERBB4 epididymis glandular cells Low Enhanced Q15303 +ENSG00000178568 ERBB4 prostate glandular cells Medium Enhanced Q15303 +ENSG00000178568 ERBB4 seminal vesicle glandular cells Medium Enhanced Q15303 +ENSG00000178568 ERBB4 testis cells in seminiferous ducts Low Enhanced Q15303 +ENSG00000178568 ERBB4 testis Leydig cells Low Enhanced Q15303 +ENSG00000178607 ERN1 epididymis glandular cells High Supported O75460 +ENSG00000178607 ERN1 prostate glandular cells Medium Supported O75460 +ENSG00000178607 ERN1 seminal vesicle glandular cells Medium Supported O75460 +ENSG00000178607 ERN1 testis cells in seminiferous ducts Medium Supported O75460 +ENSG00000178607 ERN1 testis Leydig cells Medium Supported O75460 +ENSG00000178645 C10orf53 testis elongated or late spermatids High Enhanced Q8N6V4 +ENSG00000178645 C10orf53 testis round or early spermatids Medium Enhanced Q8N6V4 +ENSG00000178662 CSRNP3 epididymis glandular cells High Supported Q8WYN3 +ENSG00000178662 CSRNP3 prostate glandular cells High Supported Q8WYN3 +ENSG00000178662 CSRNP3 seminal vesicle glandular cells High Supported Q8WYN3 +ENSG00000178662 CSRNP3 testis cells in seminiferous ducts High Supported Q8WYN3 +ENSG00000178662 CSRNP3 testis Leydig cells High Supported Q8WYN3 +ENSG00000178741 COX5A epididymis glandular cells Low Supported P20674 +ENSG00000178741 COX5A prostate glandular cells Medium Supported P20674 +ENSG00000178741 COX5A seminal vesicle glandular cells High Supported P20674 +ENSG00000178741 COX5A testis cells in seminiferous ducts High Supported P20674 +ENSG00000178741 COX5A testis Leydig cells Medium Supported P20674 +ENSG00000178764 ZHX2 epididymis glandular cells High Enhanced Q9Y6X8 +ENSG00000178764 ZHX2 seminal vesicle glandular cells High Enhanced Q9Y6X8 +ENSG00000178764 ZHX2 testis cells in seminiferous ducts Low Enhanced Q9Y6X8 +ENSG00000178764 ZHX2 testis Leydig cells Low Enhanced Q9Y6X8 +ENSG00000178804 H1FOO testis cells in seminiferous ducts High Enhanced Q8IZA3 +ENSG00000178882 RFLNA prostate glandular cells Low Enhanced Q6ZTI6 +ENSG00000178882 RFLNA testis cells in seminiferous ducts Medium Enhanced Q6ZTI6 +ENSG00000178921 PFAS epididymis glandular cells Low Enhanced O15067 +ENSG00000178921 PFAS prostate glandular cells Medium Enhanced O15067 +ENSG00000178921 PFAS seminal vesicle glandular cells Medium Enhanced O15067 +ENSG00000178921 PFAS testis cells in seminiferous ducts Medium Enhanced O15067 +ENSG00000178921 PFAS testis Leydig cells Medium Enhanced O15067 +ENSG00000178951 ZBTB7A epididymis glandular cells Medium Enhanced O95365 +ENSG00000178951 ZBTB7A prostate glandular cells Medium Enhanced O95365 +ENSG00000178951 ZBTB7A seminal vesicle glandular cells Medium Enhanced O95365 +ENSG00000178951 ZBTB7A testis cells in seminiferous ducts Medium Enhanced O95365 +ENSG00000178951 ZBTB7A testis Leydig cells Medium Enhanced O95365 +ENSG00000178952 TUFM epididymis glandular cells High Enhanced P49411 +ENSG00000178952 TUFM prostate glandular cells High Enhanced P49411 +ENSG00000178952 TUFM seminal vesicle glandular cells High Enhanced P49411 +ENSG00000178952 TUFM testis cells in seminiferous ducts High Enhanced P49411 +ENSG00000178952 TUFM testis Leydig cells High Enhanced P49411 +ENSG00000179058 C9orf50 testis elongated or late spermatids High Enhanced Q5SZB4 +ENSG00000179058 C9orf50 testis pachytene spermatocytes Medium Enhanced Q5SZB4 +ENSG00000179058 C9orf50 testis round or early spermatids High Enhanced Q5SZB4 +ENSG00000179071 CCDC89 epididymis glandular cells Low Enhanced Q8N998 +ENSG00000179071 CCDC89 testis cells in seminiferous ducts Medium Enhanced Q8N998 +ENSG00000179071 CCDC89 testis Leydig cells Low Enhanced Q8N998 +ENSG00000179091 CYC1 epididymis glandular cells Medium Supported P08574 +ENSG00000179091 CYC1 prostate glandular cells Medium Supported P08574 +ENSG00000179091 CYC1 seminal vesicle glandular cells High Supported P08574 +ENSG00000179091 CYC1 testis cells in seminiferous ducts Medium Supported P08574 +ENSG00000179091 CYC1 testis Leydig cells High Supported P08574 +ENSG00000179144 GIMAP7 epididymis glandular cells Low Enhanced Q8NHV1 +ENSG00000179163 FUCA1 epididymis glandular cells High Enhanced P04066 +ENSG00000179163 FUCA1 prostate glandular cells High Enhanced P04066 +ENSG00000179163 FUCA1 seminal vesicle glandular cells Medium Enhanced P04066 +ENSG00000179163 FUCA1 testis Leydig cells Medium Enhanced P04066 +ENSG00000179218 CALR epididymis glandular cells Medium Enhanced P27797 +ENSG00000179218 CALR prostate glandular cells Medium Enhanced P27797 +ENSG00000179218 CALR seminal vesicle glandular cells Low Enhanced P27797 +ENSG00000179218 CALR testis Leydig cells Low Enhanced P27797 +ENSG00000179262 RAD23A epididymis glandular cells Medium Supported P54725 +ENSG00000179262 RAD23A prostate glandular cells Medium Supported P54725 +ENSG00000179262 RAD23A seminal vesicle glandular cells Medium Supported P54725 +ENSG00000179262 RAD23A testis cells in seminiferous ducts High Supported P54725 +ENSG00000179262 RAD23A testis Leydig cells Medium Supported P54725 +ENSG00000179271 GADD45GIP1 epididymis glandular cells Low Supported Q8TAE8 +ENSG00000179271 GADD45GIP1 prostate glandular cells Medium Supported Q8TAE8 +ENSG00000179271 GADD45GIP1 seminal vesicle glandular cells Medium Supported Q8TAE8 +ENSG00000179271 GADD45GIP1 testis cells in seminiferous ducts Low Supported Q8TAE8 +ENSG00000179271 GADD45GIP1 testis Leydig cells Medium Supported Q8TAE8 +ENSG00000179361 ARID3B epididymis glandular cells Medium Enhanced Q8IVW6 +ENSG00000179361 ARID3B prostate glandular cells Low Enhanced Q8IVW6 +ENSG00000179361 ARID3B testis pachytene spermatocytes Medium Enhanced Q8IVW6 +ENSG00000179361 ARID3B testis preleptotene spermatocytes High Enhanced Q8IVW6 +ENSG00000179361 ARID3B testis round or early spermatids Medium Enhanced Q8IVW6 +ENSG00000179361 ARID3B testis spermatogonia High Enhanced Q8IVW6 +ENSG00000179399 GPC5 epididymis glandular cells Medium Enhanced P78333 +ENSG00000179399 GPC5 seminal vesicle glandular cells Low Enhanced P78333 +ENSG00000179399 GPC5 testis Leydig cells Medium Enhanced P78333 +ENSG00000179399 GPC5 testis peritubular cells Low Enhanced P78333 +ENSG00000179399 GPC5 testis sertoli cells High Enhanced P78333 +ENSG00000179542 SLITRK4 epididymis glandular cells Medium Enhanced Q8IW52 +ENSG00000179542 SLITRK4 testis cells in seminiferous ducts Low Enhanced Q8IW52 +ENSG00000179562 GCC1 epididymis glandular cells Medium Enhanced Q96CN9 +ENSG00000179562 GCC1 prostate glandular cells Medium Enhanced Q96CN9 +ENSG00000179562 GCC1 seminal vesicle glandular cells High Enhanced Q96CN9 +ENSG00000179562 GCC1 testis cells in seminiferous ducts Medium Enhanced Q96CN9 +ENSG00000179562 GCC1 testis Leydig cells High Enhanced Q96CN9 +ENSG00000179583 CIITA epididymis glandular cells Low Enhanced P33076 +ENSG00000179583 CIITA prostate glandular cells Low Enhanced P33076 +ENSG00000179583 CIITA seminal vesicle glandular cells Medium Enhanced P33076 +ENSG00000179588 ZFPM1 epididymis glandular cells Low Enhanced Q8IX07 +ENSG00000179588 ZFPM1 prostate glandular cells Low Enhanced Q8IX07 +ENSG00000179588 ZFPM1 seminal vesicle glandular cells Low Enhanced Q8IX07 +ENSG00000179588 ZFPM1 testis cells in seminiferous ducts High Enhanced Q8IX07 +ENSG00000179588 ZFPM1 testis Leydig cells Medium Enhanced Q8IX07 +ENSG00000179593 ALOX15B prostate glandular cells Medium Enhanced O15296 +ENSG00000179593 ALOX15B testis cells in seminiferous ducts Low Enhanced O15296 +ENSG00000179593 ALOX15B testis Leydig cells Medium Enhanced O15296 +ENSG00000179636 TPPP2 testis cells in seminiferous ducts Medium Enhanced P59282 +ENSG00000179833 SERTAD2 epididymis glandular cells High Enhanced Q14140 +ENSG00000179833 SERTAD2 prostate glandular cells Medium Enhanced Q14140 +ENSG00000179833 SERTAD2 seminal vesicle glandular cells Medium Enhanced Q14140 +ENSG00000179833 SERTAD2 testis cells in seminiferous ducts Medium Enhanced Q14140 +ENSG00000179833 SERTAD2 testis Leydig cells Medium Enhanced Q14140 +ENSG00000179902 C1orf194 testis elongated or late spermatids Medium Enhanced Q5T5A4 +ENSG00000179902 C1orf194 testis Leydig cells Low Enhanced Q5T5A4 +ENSG00000179902 C1orf194 testis pachytene spermatocytes Low Enhanced Q5T5A4 +ENSG00000179902 C1orf194 testis preleptotene spermatocytes Low Enhanced Q5T5A4 +ENSG00000179902 C1orf194 testis round or early spermatids Medium Enhanced Q5T5A4 +ENSG00000179921 GPBAR1 epididymis glandular cells Low Enhanced Q8TDU6 +ENSG00000179921 GPBAR1 prostate glandular cells Low Enhanced Q8TDU6 +ENSG00000179921 GPBAR1 seminal vesicle glandular cells Medium Enhanced Q8TDU6 +ENSG00000179950 PUF60 epididymis glandular cells Medium Enhanced H0YEM1 +ENSG00000179950 PUF60 prostate glandular cells Medium Enhanced H0YEM1 +ENSG00000179950 PUF60 seminal vesicle glandular cells Medium Enhanced H0YEM1 +ENSG00000179950 PUF60 testis cells in seminiferous ducts Medium Enhanced H0YEM1 +ENSG00000179950 PUF60 testis Leydig cells Medium Enhanced H0YEM1 +ENSG00000180185 FAHD1 epididymis glandular cells Medium Enhanced Q6P587 +ENSG00000180185 FAHD1 prostate glandular cells Medium Enhanced Q6P587 +ENSG00000180185 FAHD1 seminal vesicle glandular cells High Enhanced Q6P587 +ENSG00000180185 FAHD1 testis cells in seminiferous ducts Low Enhanced Q6P587 +ENSG00000180185 FAHD1 testis Leydig cells Medium Enhanced Q6P587 +ENSG00000180198 RCC1 epididymis glandular cells Medium Enhanced P18754 +ENSG00000180198 RCC1 prostate glandular cells Medium Enhanced P18754 +ENSG00000180198 RCC1 seminal vesicle glandular cells Medium Enhanced P18754 +ENSG00000180198 RCC1 testis cells in seminiferous ducts Medium Enhanced P18754 +ENSG00000180198 RCC1 testis Leydig cells Low Enhanced P18754 +ENSG00000180336 MEIOC testis cells in seminiferous ducts Medium Enhanced A2RUB1 +ENSG00000180398 MCFD2 epididymis glandular cells High Supported Q8NI22 +ENSG00000180398 MCFD2 prostate glandular cells High Supported Q8NI22 +ENSG00000180398 MCFD2 seminal vesicle glandular cells High Supported Q8NI22 +ENSG00000180398 MCFD2 testis cells in seminiferous ducts High Supported Q8NI22 +ENSG00000180398 MCFD2 testis Leydig cells High Supported Q8NI22 +ENSG00000180481 GLIPR1L2 testis cells in seminiferous ducts Medium Enhanced Q4G1C9 +ENSG00000180483 DEFB119 testis peritubular cells High Supported Q8N690 +ENSG00000180483 DEFB119 testis sertoli cells High Supported Q8N690 +ENSG00000180543 TSPYL5 testis cells in seminiferous ducts High Enhanced Q86VY4 +ENSG00000180573 HIST1H2AC epididymis glandular cells Medium Supported Q93077 +ENSG00000180573 HIST1H2AC prostate glandular cells Low Supported Q93077 +ENSG00000180573 HIST1H2AC seminal vesicle glandular cells Medium Supported Q93077 +ENSG00000180573 HIST1H2AC testis cells in seminiferous ducts High Supported Q93077 +ENSG00000180573 HIST1H2AC testis Leydig cells Low Supported Q93077 +ENSG00000180596 HIST1H2BC epididymis glandular cells High Supported NA +ENSG00000180596 HIST1H2BC prostate glandular cells High Supported NA +ENSG00000180596 HIST1H2BC seminal vesicle glandular cells High Supported NA +ENSG00000180596 HIST1H2BC testis cells in seminiferous ducts High Supported NA +ENSG00000180596 HIST1H2BC testis Leydig cells High Supported NA +ENSG00000180697 C3orf22 testis preleptotene spermatocytes Medium Enhanced Q8N5N4 +ENSG00000180697 C3orf22 testis spermatogonia High Enhanced Q8N5N4 +ENSG00000180773 SLC36A4 epididymis glandular cells High Enhanced Q6YBV0 +ENSG00000180773 SLC36A4 prostate glandular cells High Enhanced Q6YBV0 +ENSG00000180773 SLC36A4 seminal vesicle glandular cells Medium Enhanced Q6YBV0 +ENSG00000180773 SLC36A4 testis cells in seminiferous ducts Medium Enhanced Q6YBV0 +ENSG00000180773 SLC36A4 testis Leydig cells High Enhanced Q6YBV0 +ENSG00000180817 PPA1 epididymis glandular cells High Supported Q15181 +ENSG00000180817 PPA1 prostate glandular cells Medium Supported Q15181 +ENSG00000180817 PPA1 seminal vesicle glandular cells Medium Supported Q15181 +ENSG00000180817 PPA1 testis cells in seminiferous ducts High Supported Q15181 +ENSG00000180817 PPA1 testis Leydig cells High Supported Q15181 +ENSG00000180855 ZNF443 epididymis glandular cells Medium Supported Q9Y2A4 +ENSG00000180855 ZNF443 prostate glandular cells Medium Supported Q9Y2A4 +ENSG00000180855 ZNF443 seminal vesicle glandular cells Medium Supported Q9Y2A4 +ENSG00000180855 ZNF443 testis cells in seminiferous ducts Medium Supported Q9Y2A4 +ENSG00000180855 ZNF443 testis Leydig cells Medium Supported Q9Y2A4 +ENSG00000180878 C11orf42 testis elongated or late spermatids High Enhanced Q8N5U0 +ENSG00000180879 SSR4 epididymis glandular cells Medium Enhanced P51571 +ENSG00000180879 SSR4 prostate glandular cells Medium Enhanced P51571 +ENSG00000180879 SSR4 seminal vesicle glandular cells High Enhanced P51571 +ENSG00000180879 SSR4 testis Leydig cells Low Enhanced P51571 +ENSG00000180884 ZNF792 epididymis glandular cells High Supported Q3KQV3 +ENSG00000180884 ZNF792 prostate glandular cells High Supported Q3KQV3 +ENSG00000180884 ZNF792 seminal vesicle glandular cells Medium Supported Q3KQV3 +ENSG00000180884 ZNF792 testis cells in seminiferous ducts High Supported Q3KQV3 +ENSG00000180884 ZNF792 testis Leydig cells Medium Supported Q3KQV3 +ENSG00000180900 SCRIB epididymis glandular cells Medium Enhanced Q14160 +ENSG00000180900 SCRIB prostate glandular cells Medium Enhanced Q14160 +ENSG00000180900 SCRIB seminal vesicle glandular cells Medium Enhanced Q14160 +ENSG00000180900 SCRIB testis cells in seminiferous ducts Low Enhanced Q14160 +ENSG00000180900 SCRIB testis Leydig cells Low Enhanced Q14160 +ENSG00000180921 FAM83H prostate glandular cells Low Enhanced NA +ENSG00000180921 FAM83H seminal vesicle glandular cells Low Enhanced NA +ENSG00000180921 FAM83H testis cells in seminiferous ducts Medium Enhanced NA +ENSG00000180921 FAM83H testis Leydig cells Low Enhanced NA +ENSG00000180938 ZNF572 epididymis glandular cells Medium Enhanced Q7Z3I7 +ENSG00000180938 ZNF572 testis cells in seminiferous ducts Medium Enhanced Q7Z3I7 +ENSG00000180938 ZNF572 testis Leydig cells Medium Enhanced Q7Z3I7 +ENSG00000181019 NQO1 epididymis glandular cells Medium Enhanced P15559 +ENSG00000181019 NQO1 seminal vesicle glandular cells Low Enhanced P15559 +ENSG00000181019 NQO1 testis Leydig cells Medium Enhanced P15559 +ENSG00000181163 NPM1 epididymis glandular cells High Supported P06748 +ENSG00000181163 NPM1 prostate glandular cells High Supported P06748 +ENSG00000181163 NPM1 seminal vesicle glandular cells High Supported P06748 +ENSG00000181163 NPM1 testis cells in seminiferous ducts High Supported P06748 +ENSG00000181163 NPM1 testis Leydig cells High Supported P06748 +ENSG00000181191 PJA1 epididymis glandular cells Medium Enhanced Q8NG27 +ENSG00000181191 PJA1 prostate glandular cells High Enhanced Q8NG27 +ENSG00000181191 PJA1 seminal vesicle glandular cells Low Enhanced Q8NG27 +ENSG00000181191 PJA1 testis cells in seminiferous ducts High Enhanced Q8NG27 +ENSG00000181191 PJA1 testis Leydig cells Medium Enhanced Q8NG27 +ENSG00000181195 PENK testis spermatogonia Medium Enhanced P01210 +ENSG00000181218 HIST3H2A epididymis glandular cells Medium Supported Q7L7L0 +ENSG00000181218 HIST3H2A prostate glandular cells Low Supported Q7L7L0 +ENSG00000181218 HIST3H2A seminal vesicle glandular cells Medium Supported Q7L7L0 +ENSG00000181218 HIST3H2A testis cells in seminiferous ducts High Supported Q7L7L0 +ENSG00000181218 HIST3H2A testis Leydig cells Low Supported Q7L7L0 +ENSG00000181222 POLR2A epididymis glandular cells Medium Enhanced P24928 +ENSG00000181222 POLR2A prostate glandular cells Medium Enhanced P24928 +ENSG00000181222 POLR2A seminal vesicle glandular cells Medium Enhanced P24928 +ENSG00000181222 POLR2A testis cells in seminiferous ducts High Enhanced P24928 +ENSG00000181222 POLR2A testis Leydig cells High Enhanced P24928 +ENSG00000181322 NME9 epididymis glandular cells Medium Enhanced Q86XW9 +ENSG00000181322 NME9 prostate glandular cells Low Enhanced Q86XW9 +ENSG00000181322 NME9 seminal vesicle glandular cells Low Enhanced Q86XW9 +ENSG00000181322 NME9 testis cells in seminiferous ducts Medium Enhanced Q86XW9 +ENSG00000181409 AATK epididymis glandular cells Low Enhanced Q6ZMQ8 +ENSG00000181409 AATK seminal vesicle glandular cells Low Enhanced Q6ZMQ8 +ENSG00000181409 AATK testis cells in seminiferous ducts Medium Enhanced Q6ZMQ8 +ENSG00000181409 AATK testis Leydig cells Medium Enhanced Q6ZMQ8 +ENSG00000181433 SAGE1 testis preleptotene spermatocytes High Enhanced Q9NXZ1 +ENSG00000181433 SAGE1 testis spermatogonia High Enhanced Q9NXZ1 +ENSG00000181523 SGSH epididymis glandular cells High Enhanced P51688 +ENSG00000181523 SGSH prostate glandular cells High Enhanced P51688 +ENSG00000181523 SGSH seminal vesicle glandular cells Medium Enhanced P51688 +ENSG00000181523 SGSH testis cells in seminiferous ducts Low Enhanced P51688 +ENSG00000181523 SGSH testis Leydig cells Medium Enhanced P51688 +ENSG00000181552 EDDM3B epididymis glandular cells Low Supported P56851 +ENSG00000181610 MRPS23 epididymis glandular cells Medium Supported Q9Y3D9 +ENSG00000181610 MRPS23 prostate glandular cells Medium Supported Q9Y3D9 +ENSG00000181610 MRPS23 seminal vesicle glandular cells High Supported Q9Y3D9 +ENSG00000181610 MRPS23 testis cells in seminiferous ducts Medium Supported Q9Y3D9 +ENSG00000181610 MRPS23 testis Leydig cells High Supported Q9Y3D9 +ENSG00000181626 ANKRD62 testis Leydig cells Low Enhanced A6NC57 +ENSG00000181626 ANKRD62 testis pachytene spermatocytes Medium Enhanced A6NC57 +ENSG00000181626 ANKRD62 testis preleptotene spermatocytes Medium Enhanced A6NC57 +ENSG00000181626 ANKRD62 testis round or early spermatids Medium Enhanced A6NC57 +ENSG00000181626 ANKRD62 testis spermatogonia High Enhanced A6NC57 +ENSG00000181789 COPG1 epididymis glandular cells High Supported Q9Y678 +ENSG00000181789 COPG1 prostate glandular cells High Supported Q9Y678 +ENSG00000181789 COPG1 seminal vesicle glandular cells High Supported Q9Y678 +ENSG00000181789 COPG1 testis cells in seminiferous ducts Medium Supported Q9Y678 +ENSG00000181789 COPG1 testis Leydig cells Medium Supported Q9Y678 +ENSG00000181827 RFX7 epididymis glandular cells Medium Supported Q2KHR2 +ENSG00000181827 RFX7 prostate glandular cells Low Supported Q2KHR2 +ENSG00000181827 RFX7 seminal vesicle glandular cells Medium Supported Q2KHR2 +ENSG00000181827 RFX7 testis cells in seminiferous ducts Low Supported Q2KHR2 +ENSG00000181827 RFX7 testis Leydig cells Medium Supported Q2KHR2 +ENSG00000181830 SLC35C1 prostate glandular cells High Enhanced Q96A29 +ENSG00000181830 SLC35C1 seminal vesicle glandular cells Low Enhanced Q96A29 +ENSG00000181830 SLC35C1 testis Leydig cells Medium Enhanced Q96A29 +ENSG00000181885 CLDN7 epididymis glandular cells High Enhanced O95471 +ENSG00000181885 CLDN7 prostate glandular cells High Enhanced O95471 +ENSG00000181885 CLDN7 seminal vesicle glandular cells High Enhanced O95471 +ENSG00000181991 MRPS11 epididymis glandular cells Medium Enhanced P82912 +ENSG00000181991 MRPS11 prostate glandular cells Medium Enhanced P82912 +ENSG00000181991 MRPS11 seminal vesicle glandular cells High Enhanced P82912 +ENSG00000181991 MRPS11 testis cells in seminiferous ducts Medium Enhanced P82912 +ENSG00000181991 MRPS11 testis Leydig cells High Enhanced P82912 +ENSG00000182010 RTKN2 epididymis glandular cells Low Enhanced Q8IZC4 +ENSG00000182010 RTKN2 seminal vesicle glandular cells Low Enhanced Q8IZC4 +ENSG00000182010 RTKN2 testis cells in seminiferous ducts Low Enhanced Q8IZC4 +ENSG00000182010 RTKN2 testis Leydig cells Low Enhanced Q8IZC4 +ENSG00000182054 IDH2 prostate glandular cells High Enhanced P48735 +ENSG00000182054 IDH2 seminal vesicle glandular cells High Enhanced P48735 +ENSG00000182054 IDH2 testis cells in seminiferous ducts Medium Enhanced P48735 +ENSG00000182054 IDH2 testis Leydig cells Medium Enhanced P48735 +ENSG00000182077 PTCHD3 epididymis glandular cells Low Enhanced NA +ENSG00000182077 PTCHD3 testis elongated or late spermatids High Enhanced NA +ENSG00000182077 PTCHD3 testis Leydig cells High Enhanced NA +ENSG00000182077 PTCHD3 testis round or early spermatids Medium Enhanced NA +ENSG00000182117 NOP10 epididymis glandular cells Medium Supported Q9NPE3 +ENSG00000182117 NOP10 seminal vesicle glandular cells Medium Supported Q9NPE3 +ENSG00000182117 NOP10 testis cells in seminiferous ducts Medium Supported Q9NPE3 +ENSG00000182117 NOP10 testis Leydig cells Medium Supported Q9NPE3 +ENSG00000182154 MRPL41 epididymis glandular cells Medium Supported Q8IXM3 +ENSG00000182154 MRPL41 prostate glandular cells Medium Supported Q8IXM3 +ENSG00000182154 MRPL41 seminal vesicle glandular cells High Supported Q8IXM3 +ENSG00000182154 MRPL41 testis cells in seminiferous ducts Medium Supported Q8IXM3 +ENSG00000182154 MRPL41 testis Leydig cells High Supported Q8IXM3 +ENSG00000182180 MRPS16 epididymis glandular cells High Supported Q9Y3D3 +ENSG00000182180 MRPS16 prostate glandular cells Medium Supported Q9Y3D3 +ENSG00000182180 MRPS16 seminal vesicle glandular cells High Supported Q9Y3D3 +ENSG00000182180 MRPS16 testis cells in seminiferous ducts Medium Supported Q9Y3D3 +ENSG00000182180 MRPS16 testis Leydig cells High Supported Q9Y3D3 +ENSG00000182185 RAD51B epididymis glandular cells High Enhanced O15315 +ENSG00000182185 RAD51B prostate glandular cells Medium Enhanced O15315 +ENSG00000182185 RAD51B seminal vesicle glandular cells High Enhanced O15315 +ENSG00000182185 RAD51B testis cells in seminiferous ducts High Enhanced O15315 +ENSG00000182185 RAD51B testis Leydig cells High Enhanced O15315 +ENSG00000182199 SHMT2 epididymis glandular cells Low Enhanced P34897 +ENSG00000182199 SHMT2 prostate glandular cells Medium Enhanced P34897 +ENSG00000182199 SHMT2 seminal vesicle glandular cells Medium Enhanced P34897 +ENSG00000182199 SHMT2 testis Leydig cells Medium Enhanced P34897 +ENSG00000182256 GABRG3 epididymis glandular cells Low Supported Q99928 +ENSG00000182256 GABRG3 prostate glandular cells Low Supported Q99928 +ENSG00000182256 GABRG3 testis cells in seminiferous ducts Low Supported Q99928 +ENSG00000182264 IZUMO1 testis elongated or late spermatids High Enhanced Q8IYV9 +ENSG00000182264 IZUMO1 testis Leydig cells Low Enhanced Q8IYV9 +ENSG00000182264 IZUMO1 testis round or early spermatids High Enhanced Q8IYV9 +ENSG00000182287 AP1S2 epididymis glandular cells Medium Enhanced P56377 +ENSG00000182287 AP1S2 seminal vesicle glandular cells Low Enhanced P56377 +ENSG00000182287 AP1S2 testis cells in seminiferous ducts Medium Enhanced P56377 +ENSG00000182287 AP1S2 testis Leydig cells Medium Enhanced P56377 +ENSG00000182308 DCAF4L1 testis elongated or late spermatids Low Enhanced Q3SXM0 +ENSG00000182308 DCAF4L1 testis pachytene spermatocytes Low Enhanced Q3SXM0 +ENSG00000182308 DCAF4L1 testis peritubular cells Low Enhanced Q3SXM0 +ENSG00000182308 DCAF4L1 testis preleptotene spermatocytes High Enhanced Q3SXM0 +ENSG00000182308 DCAF4L1 testis round or early spermatids Low Enhanced Q3SXM0 +ENSG00000182308 DCAF4L1 testis spermatogonia High Enhanced Q3SXM0 +ENSG00000182446 NPLOC4 epididymis glandular cells Medium Enhanced Q8TAT6 +ENSG00000182446 NPLOC4 prostate glandular cells Medium Enhanced Q8TAT6 +ENSG00000182446 NPLOC4 seminal vesicle glandular cells Low Enhanced Q8TAT6 +ENSG00000182446 NPLOC4 testis cells in seminiferous ducts High Enhanced Q8TAT6 +ENSG00000182446 NPLOC4 testis Leydig cells High Enhanced Q8TAT6 +ENSG00000182459 TEX19 testis sertoli cells High Enhanced Q8NA77 +ENSG00000182473 EXOC7 epididymis glandular cells Medium Supported Q9UPT5 +ENSG00000182473 EXOC7 prostate glandular cells Medium Supported Q9UPT5 +ENSG00000182473 EXOC7 seminal vesicle glandular cells Medium Supported Q9UPT5 +ENSG00000182473 EXOC7 testis cells in seminiferous ducts Medium Supported Q9UPT5 +ENSG00000182473 EXOC7 testis Leydig cells Medium Supported Q9UPT5 +ENSG00000182481 KPNA2 epididymis glandular cells Low Enhanced P52292 +ENSG00000182481 KPNA2 seminal vesicle glandular cells Low Enhanced P52292 +ENSG00000182481 KPNA2 testis cells in seminiferous ducts High Enhanced P52292 +ENSG00000182481 KPNA2 testis Leydig cells Medium Enhanced P52292 +ENSG00000182492 BGN epididymis glandular cells Medium Enhanced P21810 +ENSG00000182504 CEP97 epididymis glandular cells High Enhanced Q8IW35 +ENSG00000182504 CEP97 prostate glandular cells Low Enhanced Q8IW35 +ENSG00000182504 CEP97 seminal vesicle glandular cells Low Enhanced Q8IW35 +ENSG00000182504 CEP97 testis cells in seminiferous ducts High Enhanced Q8IW35 +ENSG00000182533 CAV3 testis Leydig cells Low Enhanced P56539 +ENSG00000182568 SATB1 epididymis glandular cells Medium Supported Q01826 +ENSG00000182568 SATB1 seminal vesicle glandular cells Medium Supported Q01826 +ENSG00000182568 SATB1 testis cells in seminiferous ducts Low Supported Q01826 +ENSG00000182580 EPHB3 epididymis glandular cells Low Enhanced P54753 +ENSG00000182580 EPHB3 prostate glandular cells Medium Enhanced P54753 +ENSG00000182580 EPHB3 seminal vesicle glandular cells Medium Enhanced P54753 +ENSG00000182580 EPHB3 testis cells in seminiferous ducts Medium Enhanced P54753 +ENSG00000182580 EPHB3 testis Leydig cells Medium Enhanced P54753 +ENSG00000182583 VCX testis elongated or late spermatids Medium Supported Q9H320 +ENSG00000182583 VCX testis pachytene spermatocytes High Supported Q9H320 +ENSG00000182583 VCX testis preleptotene spermatocytes High Supported Q9H320 +ENSG00000182583 VCX testis round or early spermatids High Supported Q9H320 +ENSG00000182583 VCX testis spermatogonia High Supported Q9H320 +ENSG00000182718 ANXA2 prostate glandular cells Medium Enhanced P07355 +ENSG00000182718 ANXA2 seminal vesicle glandular cells High Enhanced P07355 +ENSG00000182718 ANXA2 testis Leydig cells Low Enhanced P07355 +ENSG00000182795 C1orf116 epididymis glandular cells Medium Enhanced Q9BW04 +ENSG00000182795 C1orf116 prostate glandular cells High Enhanced Q9BW04 +ENSG00000182795 C1orf116 seminal vesicle glandular cells Medium Enhanced Q9BW04 +ENSG00000182916 TCEAL7 testis cells in seminiferous ducts Low Enhanced Q9BRU2 +ENSG00000182944 EWSR1 epididymis glandular cells High Enhanced Q01844 +ENSG00000182944 EWSR1 prostate glandular cells High Enhanced Q01844 +ENSG00000182944 EWSR1 seminal vesicle glandular cells High Enhanced Q01844 +ENSG00000182944 EWSR1 testis cells in seminiferous ducts High Enhanced Q01844 +ENSG00000182944 EWSR1 testis Leydig cells High Enhanced Q01844 +ENSG00000182979 MTA1 epididymis glandular cells Low Supported Q13330 +ENSG00000182979 MTA1 seminal vesicle glandular cells Low Supported Q13330 +ENSG00000182979 MTA1 testis cells in seminiferous ducts High Supported Q13330 +ENSG00000182979 MTA1 testis Leydig cells High Supported Q13330 +ENSG00000182985 CADM1 epididymis glandular cells High Enhanced Q9BY67 +ENSG00000182985 CADM1 prostate glandular cells Medium Enhanced Q9BY67 +ENSG00000182985 CADM1 seminal vesicle glandular cells Low Enhanced Q9BY67 +ENSG00000182985 CADM1 testis cells in seminiferous ducts Medium Enhanced Q9BY67 +ENSG00000183020 AP2A2 epididymis glandular cells Medium Enhanced O94973 +ENSG00000183020 AP2A2 prostate glandular cells Medium Enhanced O94973 +ENSG00000183020 AP2A2 seminal vesicle glandular cells Medium Enhanced O94973 +ENSG00000183020 AP2A2 testis cells in seminiferous ducts High Enhanced O94973 +ENSG00000183020 AP2A2 testis Leydig cells High Enhanced O94973 +ENSG00000183035 CYLC1 testis cells in seminiferous ducts Medium Enhanced P35663 +ENSG00000183044 ABAT epididymis glandular cells Low Enhanced P80404 +ENSG00000183044 ABAT prostate glandular cells Medium Enhanced P80404 +ENSG00000183044 ABAT seminal vesicle glandular cells Medium Enhanced P80404 +ENSG00000183044 ABAT testis cells in seminiferous ducts Low Enhanced P80404 +ENSG00000183044 ABAT testis Leydig cells Low Enhanced P80404 +ENSG00000183048 SLC25A10 epididymis glandular cells Medium Supported Q9UBX3 +ENSG00000183048 SLC25A10 prostate glandular cells Low Supported Q9UBX3 +ENSG00000183048 SLC25A10 seminal vesicle glandular cells Medium Supported Q9UBX3 +ENSG00000183048 SLC25A10 testis cells in seminiferous ducts High Supported Q9UBX3 +ENSG00000183048 SLC25A10 testis Leydig cells Medium Supported Q9UBX3 +ENSG00000183049 CAMK1D epididymis glandular cells Medium Enhanced Q8IU85 +ENSG00000183049 CAMK1D prostate glandular cells Medium Enhanced Q8IU85 +ENSG00000183049 CAMK1D seminal vesicle glandular cells Medium Enhanced Q8IU85 +ENSG00000183049 CAMK1D testis cells in seminiferous ducts Medium Enhanced Q8IU85 +ENSG00000183049 CAMK1D testis Leydig cells Medium Enhanced Q8IU85 +ENSG00000183066 WBP2NL testis elongated or late spermatids High Enhanced Q6ICG8 +ENSG00000183160 TMEM119 epididymis glandular cells Low Enhanced Q4V9L6 +ENSG00000183160 TMEM119 prostate glandular cells Low Enhanced Q4V9L6 +ENSG00000183160 TMEM119 seminal vesicle glandular cells Low Enhanced Q4V9L6 +ENSG00000183207 RUVBL2 testis cells in seminiferous ducts High Enhanced Q9Y230 +ENSG00000183246 RIMBP3C testis elongated or late spermatids High Supported A6NJZ7 +ENSG00000183246 RIMBP3C testis Leydig cells Low Supported A6NJZ7 +ENSG00000183246 RIMBP3C testis pachytene spermatocytes High Supported A6NJZ7 +ENSG00000183246 RIMBP3C testis preleptotene spermatocytes Low Supported A6NJZ7 +ENSG00000183246 RIMBP3C testis round or early spermatids High Supported A6NJZ7 +ENSG00000183246 RIMBP3C testis spermatogonia Low Supported A6NJZ7 +ENSG00000183258 DDX41 epididymis glandular cells High Enhanced Q9UJV9 +ENSG00000183258 DDX41 prostate glandular cells Medium Enhanced Q9UJV9 +ENSG00000183258 DDX41 seminal vesicle glandular cells High Enhanced Q9UJV9 +ENSG00000183258 DDX41 testis cells in seminiferous ducts High Enhanced Q9UJV9 +ENSG00000183258 DDX41 testis Leydig cells Medium Enhanced Q9UJV9 +ENSG00000183318 SPDYE4 testis cells in seminiferous ducts Medium Enhanced A6NLX3 +ENSG00000183318 SPDYE4 testis elongated or late spermatids High Enhanced A6NLX3 +ENSG00000183318 SPDYE4 testis round or early spermatids Medium Enhanced A6NLX3 +ENSG00000183336 BOLA2 epididymis glandular cells Low Supported A0A087WZT3 +ENSG00000183336 BOLA2 prostate glandular cells Low Supported A0A087WZT3 +ENSG00000183336 BOLA2 seminal vesicle glandular cells Medium Supported A0A087WZT3 +ENSG00000183336 BOLA2 testis cells in seminiferous ducts Medium Supported A0A087WZT3 +ENSG00000183336 BOLA2 testis Leydig cells Medium Supported A0A087WZT3 +ENSG00000183346 C10orf107 testis elongated or late spermatids High Enhanced Q8IVU9 +ENSG00000183346 C10orf107 testis Leydig cells Low Enhanced Q8IVU9 +ENSG00000183346 C10orf107 testis pachytene spermatocytes Low Enhanced Q8IVU9 +ENSG00000183346 C10orf107 testis round or early spermatids High Enhanced Q8IVU9 +ENSG00000183347 GBP6 testis Leydig cells Low Enhanced Q6ZN66 +ENSG00000183421 RIPK4 testis Leydig cells Low Enhanced P57078 +ENSG00000183426 NPIPA1 epididymis glandular cells High Supported Q9UND3 +ENSG00000183426 NPIPA1 prostate glandular cells Medium Supported Q9UND3 +ENSG00000183426 NPIPA1 seminal vesicle glandular cells Medium Supported Q9UND3 +ENSG00000183426 NPIPA1 testis Leydig cells Medium Supported Q9UND3 +ENSG00000183431 SF3A3 epididymis glandular cells High Enhanced Q12874 +ENSG00000183431 SF3A3 prostate glandular cells Medium Enhanced Q12874 +ENSG00000183431 SF3A3 seminal vesicle glandular cells Medium Enhanced Q12874 +ENSG00000183431 SF3A3 testis cells in seminiferous ducts High Enhanced Q12874 +ENSG00000183431 SF3A3 testis Leydig cells High Enhanced Q12874 +ENSG00000183475 ASB7 epididymis glandular cells Medium Enhanced Q9H672 +ENSG00000183475 ASB7 seminal vesicle glandular cells Low Enhanced Q9H672 +ENSG00000183475 ASB7 testis Leydig cells Low Enhanced Q9H672 +ENSG00000183484 GPR132 epididymis glandular cells High Supported Q9UNW8 +ENSG00000183484 GPR132 prostate glandular cells Low Supported Q9UNW8 +ENSG00000183484 GPR132 seminal vesicle glandular cells Medium Supported Q9UNW8 +ENSG00000183484 GPR132 testis cells in seminiferous ducts Medium Supported Q9UNW8 +ENSG00000183484 GPR132 testis Leydig cells Medium Supported Q9UNW8 +ENSG00000183495 EP400 epididymis glandular cells High Supported Q96L91 +ENSG00000183495 EP400 prostate glandular cells Low Supported Q96L91 +ENSG00000183495 EP400 seminal vesicle glandular cells High Supported Q96L91 +ENSG00000183495 EP400 testis cells in seminiferous ducts High Supported Q96L91 +ENSG00000183495 EP400 testis Leydig cells Medium Supported Q96L91 +ENSG00000183496 MEX3B testis elongated or late spermatids High Enhanced Q6ZN04 +ENSG00000183496 MEX3B testis Leydig cells Low Enhanced Q6ZN04 +ENSG00000183496 MEX3B testis pachytene spermatocytes Low Enhanced Q6ZN04 +ENSG00000183496 MEX3B testis round or early spermatids Low Enhanced Q6ZN04 +ENSG00000183598 HIST2H3D epididymis glandular cells High Supported NA +ENSG00000183598 HIST2H3D prostate glandular cells High Supported NA +ENSG00000183598 HIST2H3D seminal vesicle glandular cells High Supported NA +ENSG00000183598 HIST2H3D testis cells in seminiferous ducts High Supported NA +ENSG00000183598 HIST2H3D testis Leydig cells High Supported NA +ENSG00000183684 ALYREF epididymis glandular cells High Supported Q86V81 +ENSG00000183684 ALYREF prostate glandular cells High Supported Q86V81 +ENSG00000183684 ALYREF seminal vesicle glandular cells High Supported Q86V81 +ENSG00000183684 ALYREF testis cells in seminiferous ducts High Supported Q86V81 +ENSG00000183684 ALYREF testis Leydig cells Medium Supported Q86V81 +ENSG00000183723 CMTM4 epididymis glandular cells Medium Enhanced Q8IZR5 +ENSG00000183723 CMTM4 prostate glandular cells Medium Enhanced Q8IZR5 +ENSG00000183723 CMTM4 seminal vesicle glandular cells Low Enhanced Q8IZR5 +ENSG00000183723 CMTM4 testis cells in seminiferous ducts Medium Enhanced Q8IZR5 +ENSG00000183723 CMTM4 testis Leydig cells Medium Enhanced Q8IZR5 +ENSG00000183742 MACC1 epididymis glandular cells Low Supported Q6ZN28 +ENSG00000183742 MACC1 prostate glandular cells High Supported Q6ZN28 +ENSG00000183742 MACC1 seminal vesicle glandular cells High Supported Q6ZN28 +ENSG00000183742 MACC1 testis cells in seminiferous ducts High Supported Q6ZN28 +ENSG00000183742 MACC1 testis Leydig cells High Supported Q6ZN28 +ENSG00000183751 TBL3 epididymis glandular cells Low Enhanced Q12788 +ENSG00000183751 TBL3 testis cells in seminiferous ducts Medium Enhanced Q12788 +ENSG00000183751 TBL3 testis Leydig cells Low Enhanced Q12788 +ENSG00000183763 TRAIP epididymis glandular cells Medium Enhanced Q9BWF2 +ENSG00000183763 TRAIP prostate glandular cells Low Enhanced Q9BWF2 +ENSG00000183763 TRAIP seminal vesicle glandular cells Medium Enhanced Q9BWF2 +ENSG00000183763 TRAIP testis cells in seminiferous ducts High Enhanced Q9BWF2 +ENSG00000183763 TRAIP testis Leydig cells High Enhanced Q9BWF2 +ENSG00000183765 CHEK2 epididymis glandular cells High Enhanced O96017 +ENSG00000183765 CHEK2 testis cells in seminiferous ducts Medium Enhanced O96017 +ENSG00000183765 CHEK2 testis Leydig cells High Enhanced O96017 +ENSG00000183779 ZNF703 epididymis glandular cells Medium Supported Q9H7S9 +ENSG00000183779 ZNF703 prostate glandular cells Medium Supported Q9H7S9 +ENSG00000183779 ZNF703 seminal vesicle glandular cells Low Supported Q9H7S9 +ENSG00000183779 ZNF703 testis cells in seminiferous ducts Medium Supported Q9H7S9 +ENSG00000183779 ZNF703 testis Leydig cells Medium Supported Q9H7S9 +ENSG00000183831 ANKRD45 testis elongated or late spermatids Medium Enhanced Q5TZF3 +ENSG00000183831 ANKRD45 testis pachytene spermatocytes Low Enhanced Q5TZF3 +ENSG00000183831 ANKRD45 testis round or early spermatids Medium Enhanced Q5TZF3 +ENSG00000183878 UTY seminal vesicle glandular cells Low Supported O14607 +ENSG00000183878 UTY testis cells in seminiferous ducts Low Supported O14607 +ENSG00000183914 DNAH2 testis preleptotene spermatocytes Low Enhanced Q9P225 +ENSG00000183914 DNAH2 testis spermatogonia Medium Enhanced Q9P225 +ENSG00000183943 PRKX epididymis glandular cells High Supported P51817 +ENSG00000183943 PRKX prostate glandular cells Medium Supported P51817 +ENSG00000183943 PRKX seminal vesicle glandular cells Low Supported P51817 +ENSG00000183943 PRKX testis cells in seminiferous ducts Medium Supported P51817 +ENSG00000183943 PRKX testis Leydig cells High Supported P51817 +ENSG00000183977 PP2D1 testis cells in seminiferous ducts Medium Supported A8MPX8 +ENSG00000184012 TMPRSS2 epididymis glandular cells Medium Enhanced O15393 +ENSG00000184012 TMPRSS2 prostate glandular cells Medium Enhanced O15393 +ENSG00000184012 TMPRSS2 seminal vesicle glandular cells Low Enhanced O15393 +ENSG00000184033 CTAG1B testis pachytene spermatocytes High Enhanced NA +ENSG00000184033 CTAG1B testis preleptotene spermatocytes High Enhanced NA +ENSG00000184033 CTAG1B testis round or early spermatids Medium Enhanced NA +ENSG00000184033 CTAG1B testis spermatogonia High Enhanced NA +ENSG00000184047 DIABLO epididymis glandular cells Medium Enhanced Q9NR28 +ENSG00000184047 DIABLO prostate glandular cells Medium Enhanced Q9NR28 +ENSG00000184047 DIABLO seminal vesicle glandular cells Medium Enhanced Q9NR28 +ENSG00000184047 DIABLO testis cells in seminiferous ducts High Enhanced Q9NR28 +ENSG00000184047 DIABLO testis Leydig cells Medium Enhanced Q9NR28 +ENSG00000184110 EIF3C epididymis glandular cells High Supported Q99613 +ENSG00000184110 EIF3C prostate glandular cells Medium Supported Q99613 +ENSG00000184110 EIF3C seminal vesicle glandular cells Medium Supported Q99613 +ENSG00000184110 EIF3C testis cells in seminiferous ducts Medium Supported Q99613 +ENSG00000184110 EIF3C testis Leydig cells High Supported Q99613 +ENSG00000184178 SCFD2 epididymis glandular cells Medium Enhanced Q8WU76 +ENSG00000184178 SCFD2 prostate glandular cells Low Enhanced Q8WU76 +ENSG00000184178 SCFD2 seminal vesicle glandular cells Medium Enhanced Q8WU76 +ENSG00000184178 SCFD2 testis cells in seminiferous ducts Medium Enhanced Q8WU76 +ENSG00000184178 SCFD2 testis Leydig cells Medium Enhanced Q8WU76 +ENSG00000184209 SNRNP35 epididymis glandular cells Medium Supported Q16560 +ENSG00000184209 SNRNP35 prostate glandular cells Medium Supported Q16560 +ENSG00000184209 SNRNP35 seminal vesicle glandular cells Medium Supported Q16560 +ENSG00000184209 SNRNP35 testis cells in seminiferous ducts Medium Supported Q16560 +ENSG00000184209 SNRNP35 testis Leydig cells Medium Supported Q16560 +ENSG00000184216 IRAK1 epididymis glandular cells Low Supported P51617 +ENSG00000184216 IRAK1 prostate glandular cells Medium Supported P51617 +ENSG00000184216 IRAK1 seminal vesicle glandular cells Low Supported P51617 +ENSG00000184216 IRAK1 testis cells in seminiferous ducts Medium Supported P51617 +ENSG00000184216 IRAK1 testis Leydig cells Medium Supported P51617 +ENSG00000184254 ALDH1A3 epididymis glandular cells Low Enhanced P47895 +ENSG00000184254 ALDH1A3 prostate glandular cells High Enhanced P47895 +ENSG00000184254 ALDH1A3 seminal vesicle glandular cells Low Enhanced P47895 +ENSG00000184254 ALDH1A3 testis cells in seminiferous ducts Low Enhanced P47895 +ENSG00000184254 ALDH1A3 testis Leydig cells Low Enhanced P47895 +ENSG00000184260 HIST2H2AC epididymis glandular cells Medium Supported Q16777 +ENSG00000184260 HIST2H2AC prostate glandular cells Low Supported Q16777 +ENSG00000184260 HIST2H2AC seminal vesicle glandular cells Medium Supported Q16777 +ENSG00000184260 HIST2H2AC testis cells in seminiferous ducts High Supported Q16777 +ENSG00000184260 HIST2H2AC testis Leydig cells Low Supported Q16777 +ENSG00000184270 HIST2H2AB epididymis glandular cells Medium Supported Q8IUE6 +ENSG00000184270 HIST2H2AB prostate glandular cells Low Supported Q8IUE6 +ENSG00000184270 HIST2H2AB seminal vesicle glandular cells Medium Supported Q8IUE6 +ENSG00000184270 HIST2H2AB testis cells in seminiferous ducts High Supported Q8IUE6 +ENSG00000184270 HIST2H2AB testis Leydig cells Low Supported Q8IUE6 +ENSG00000184271 POU6F1 epididymis glandular cells High Enhanced Q14863 +ENSG00000184271 POU6F1 prostate glandular cells Medium Enhanced Q14863 +ENSG00000184271 POU6F1 seminal vesicle glandular cells Medium Enhanced Q14863 +ENSG00000184271 POU6F1 testis cells in seminiferous ducts High Enhanced Q14863 +ENSG00000184271 POU6F1 testis Leydig cells High Enhanced Q14863 +ENSG00000184292 TACSTD2 epididymis glandular cells Low Enhanced P09758 +ENSG00000184292 TACSTD2 seminal vesicle glandular cells Medium Enhanced P09758 +ENSG00000184313 MROH7 testis cells in seminiferous ducts Medium Enhanced Q68CQ1 +ENSG00000184363 PKP3 testis cells in seminiferous ducts Low Enhanced Q9Y446 +ENSG00000184363 PKP3 testis Leydig cells Medium Enhanced Q9Y446 +ENSG00000184368 MAP7D2 testis cells in seminiferous ducts Medium Enhanced Q96T17 +ENSG00000184368 MAP7D2 testis Leydig cells Low Enhanced Q96T17 +ENSG00000184470 TXNRD2 epididymis glandular cells Medium Supported Q9NNW7 +ENSG00000184470 TXNRD2 prostate glandular cells Medium Supported Q9NNW7 +ENSG00000184470 TXNRD2 seminal vesicle glandular cells Medium Supported Q9NNW7 +ENSG00000184470 TXNRD2 testis cells in seminiferous ducts Medium Supported Q9NNW7 +ENSG00000184470 TXNRD2 testis Leydig cells Medium Supported Q9NNW7 +ENSG00000184500 PROS1 testis cells in seminiferous ducts Low Enhanced P07225 +ENSG00000184500 PROS1 testis Leydig cells Medium Enhanced P07225 +ENSG00000184507 NUTM1 testis elongated or late spermatids Low Enhanced Q86Y26 +ENSG00000184507 NUTM1 testis Leydig cells Low Enhanced Q86Y26 +ENSG00000184507 NUTM1 testis preleptotene spermatocytes Medium Enhanced Q86Y26 +ENSG00000184507 NUTM1 testis round or early spermatids High Enhanced Q86Y26 +ENSG00000184507 NUTM1 testis spermatogonia High Enhanced Q86Y26 +ENSG00000184584 TMEM173 epididymis glandular cells Medium Enhanced Q86WV6 +ENSG00000184584 TMEM173 prostate glandular cells Medium Enhanced Q86WV6 +ENSG00000184584 TMEM173 seminal vesicle glandular cells Medium Enhanced Q86WV6 +ENSG00000184584 TMEM173 testis Leydig cells Medium Enhanced Q86WV6 +ENSG00000184634 MED12 epididymis glandular cells High Enhanced Q93074 +ENSG00000184634 MED12 prostate glandular cells High Enhanced Q93074 +ENSG00000184634 MED12 seminal vesicle glandular cells High Enhanced Q93074 +ENSG00000184634 MED12 testis cells in seminiferous ducts High Enhanced Q93074 +ENSG00000184634 MED12 testis Leydig cells High Enhanced Q93074 +ENSG00000184678 HIST2H2BE epididymis glandular cells High Supported Q16778 +ENSG00000184678 HIST2H2BE prostate glandular cells High Supported Q16778 +ENSG00000184678 HIST2H2BE seminal vesicle glandular cells High Supported Q16778 +ENSG00000184678 HIST2H2BE testis cells in seminiferous ducts High Supported Q16778 +ENSG00000184678 HIST2H2BE testis Leydig cells Medium Supported Q16778 +ENSG00000184708 EIF4ENIF1 epididymis glandular cells High Enhanced Q9NRA8 +ENSG00000184708 EIF4ENIF1 prostate glandular cells High Enhanced Q9NRA8 +ENSG00000184708 EIF4ENIF1 seminal vesicle glandular cells High Enhanced Q9NRA8 +ENSG00000184708 EIF4ENIF1 testis cells in seminiferous ducts High Enhanced Q9NRA8 +ENSG00000184708 EIF4ENIF1 testis Leydig cells High Enhanced Q9NRA8 +ENSG00000184730 APOBR epididymis glandular cells Low Enhanced Q0VD83 +ENSG00000184730 APOBR prostate glandular cells Low Enhanced Q0VD83 +ENSG00000184730 APOBR seminal vesicle glandular cells Low Enhanced Q0VD83 +ENSG00000184730 APOBR testis cells in seminiferous ducts Low Enhanced Q0VD83 +ENSG00000184730 APOBR testis Leydig cells Low Enhanced Q0VD83 +ENSG00000184752 NDUFA12 epididymis glandular cells High Supported Q9UI09 +ENSG00000184752 NDUFA12 prostate glandular cells High Supported Q9UI09 +ENSG00000184752 NDUFA12 seminal vesicle glandular cells High Supported Q9UI09 +ENSG00000184752 NDUFA12 testis cells in seminiferous ducts High Supported Q9UI09 +ENSG00000184752 NDUFA12 testis Leydig cells High Supported Q9UI09 +ENSG00000184831 APOO epididymis glandular cells High Supported Q9BUR5 +ENSG00000184831 APOO prostate glandular cells Medium Supported Q9BUR5 +ENSG00000184831 APOO seminal vesicle glandular cells High Supported Q9BUR5 +ENSG00000184831 APOO testis cells in seminiferous ducts Medium Supported Q9BUR5 +ENSG00000184831 APOO testis Leydig cells Medium Supported Q9BUR5 +ENSG00000184867 ARMCX2 epididymis glandular cells High Enhanced Q7L311 +ENSG00000184867 ARMCX2 prostate glandular cells Medium Enhanced Q7L311 +ENSG00000184867 ARMCX2 seminal vesicle glandular cells Medium Enhanced Q7L311 +ENSG00000184867 ARMCX2 testis Leydig cells Medium Enhanced Q7L311 +ENSG00000184897 H1FX epididymis glandular cells Medium Supported Q92522 +ENSG00000184897 H1FX prostate glandular cells Medium Supported Q92522 +ENSG00000184897 H1FX seminal vesicle glandular cells Medium Supported Q92522 +ENSG00000184897 H1FX testis cells in seminiferous ducts Medium Supported Q92522 +ENSG00000184897 H1FX testis Leydig cells Medium Supported Q92522 +ENSG00000184900 SUMO3 epididymis glandular cells Medium Supported P55854 +ENSG00000184900 SUMO3 prostate glandular cells Medium Supported P55854 +ENSG00000184900 SUMO3 seminal vesicle glandular cells Medium Supported P55854 +ENSG00000184900 SUMO3 testis cells in seminiferous ducts High Supported P55854 +ENSG00000184900 SUMO3 testis Leydig cells Medium Supported P55854 +ENSG00000184937 WT1 epididymis glandular cells Low Enhanced P19544 +ENSG00000184937 WT1 prostate glandular cells Low Enhanced P19544 +ENSG00000184937 WT1 seminal vesicle glandular cells Low Enhanced P19544 +ENSG00000184937 WT1 testis cells in seminiferous ducts High Enhanced P19544 +ENSG00000184945 AQP12A epididymis glandular cells High Supported Q8IXF9 +ENSG00000184956 MUC6 seminal vesicle glandular cells High Enhanced H0YEZ6 +ENSG00000185000 DGAT1 seminal vesicle glandular cells Low Enhanced O75907 +ENSG00000185000 DGAT1 testis cells in seminiferous ducts Medium Enhanced O75907 +ENSG00000185000 DGAT1 testis Leydig cells Low Enhanced O75907 +ENSG00000185010 F8 epididymis glandular cells Medium Enhanced P00451 +ENSG00000185010 F8 prostate glandular cells Medium Enhanced P00451 +ENSG00000185010 F8 seminal vesicle glandular cells Medium Enhanced P00451 +ENSG00000185010 F8 testis cells in seminiferous ducts Low Enhanced P00451 +ENSG00000185010 F8 testis Leydig cells Medium Enhanced P00451 +ENSG00000185015 CA13 epididymis glandular cells Low Enhanced Q8N1Q1 +ENSG00000185015 CA13 prostate glandular cells Low Enhanced Q8N1Q1 +ENSG00000185015 CA13 seminal vesicle glandular cells Medium Enhanced Q8N1Q1 +ENSG00000185015 CA13 testis cells in seminiferous ducts Low Enhanced Q8N1Q1 +ENSG00000185015 CA13 testis Leydig cells Medium Enhanced Q8N1Q1 +ENSG00000185040 SPDYE16 testis cells in seminiferous ducts Medium Supported A6NNV3 +ENSG00000185049 NELFA epididymis glandular cells High Enhanced Q9H3P2 +ENSG00000185049 NELFA prostate glandular cells High Enhanced Q9H3P2 +ENSG00000185049 NELFA seminal vesicle glandular cells Medium Enhanced Q9H3P2 +ENSG00000185049 NELFA testis cells in seminiferous ducts High Enhanced Q9H3P2 +ENSG00000185049 NELFA testis Leydig cells High Enhanced Q9H3P2 +ENSG00000185122 HSF1 epididymis glandular cells High Supported Q00613 +ENSG00000185122 HSF1 prostate glandular cells Medium Supported Q00613 +ENSG00000185122 HSF1 seminal vesicle glandular cells Medium Supported Q00613 +ENSG00000185122 HSF1 testis cells in seminiferous ducts Medium Supported Q00613 +ENSG00000185122 HSF1 testis Leydig cells Medium Supported Q00613 +ENSG00000185130 HIST1H2BL epididymis glandular cells High Supported Q99880 +ENSG00000185130 HIST1H2BL prostate glandular cells High Supported Q99880 +ENSG00000185130 HIST1H2BL seminal vesicle glandular cells High Supported Q99880 +ENSG00000185130 HIST1H2BL testis cells in seminiferous ducts High Supported Q99880 +ENSG00000185130 HIST1H2BL testis Leydig cells High Supported Q99880 +ENSG00000185176 AQP12B epididymis glandular cells High Supported A6NM10 +ENSG00000185215 TNFAIP2 prostate glandular cells Low Enhanced Q03169 +ENSG00000185215 TNFAIP2 seminal vesicle glandular cells Low Enhanced Q03169 +ENSG00000185215 TNFAIP2 testis cells in seminiferous ducts Low Enhanced Q03169 +ENSG00000185215 TNFAIP2 testis Leydig cells Low Enhanced Q03169 +ENSG00000185264 TEX33 testis elongated or late spermatids High Enhanced O43247 +ENSG00000185264 TEX33 testis pachytene spermatocytes Low Enhanced O43247 +ENSG00000185264 TEX33 testis peritubular cells Low Enhanced O43247 +ENSG00000185264 TEX33 testis preleptotene spermatocytes Low Enhanced O43247 +ENSG00000185264 TEX33 testis round or early spermatids Low Enhanced O43247 +ENSG00000185264 TEX33 testis spermatogonia Medium Enhanced O43247 +ENSG00000185306 C12orf56 testis elongated or late spermatids Medium Enhanced Q8IXR9 +ENSG00000185306 C12orf56 testis sertoli cells Medium Enhanced Q8IXR9 +ENSG00000185345 PARK2 epididymis glandular cells Medium Enhanced O60260 +ENSG00000185345 PARK2 seminal vesicle glandular cells Low Enhanced O60260 +ENSG00000185345 PARK2 testis cells in seminiferous ducts Medium Enhanced O60260 +ENSG00000185345 PARK2 testis Leydig cells High Enhanced O60260 +ENSG00000185499 MUC1 epididymis glandular cells Medium Enhanced P15941 +ENSG00000185499 MUC1 prostate glandular cells Low Enhanced P15941 +ENSG00000185499 MUC1 seminal vesicle glandular cells Medium Enhanced P15941 +ENSG00000185499 MUC1 testis cells in seminiferous ducts Low Enhanced P15941 +ENSG00000185499 MUC1 testis Leydig cells Low Enhanced P15941 +ENSG00000185532 PRKG1 epididymis glandular cells Medium Enhanced Q13976 +ENSG00000185532 PRKG1 prostate glandular cells Medium Enhanced Q13976 +ENSG00000185532 PRKG1 seminal vesicle glandular cells Medium Enhanced Q13976 +ENSG00000185532 PRKG1 testis cells in seminiferous ducts Medium Enhanced Q13976 +ENSG00000185532 PRKG1 testis Leydig cells Medium Enhanced Q13976 +ENSG00000185591 SP1 epididymis glandular cells Medium Supported P08047 +ENSG00000185591 SP1 prostate glandular cells Medium Supported P08047 +ENSG00000185591 SP1 seminal vesicle glandular cells Medium Supported P08047 +ENSG00000185591 SP1 testis cells in seminiferous ducts Medium Supported P08047 +ENSG00000185591 SP1 testis Leydig cells Medium Supported P08047 +ENSG00000185624 P4HB epididymis glandular cells High Enhanced P07237 +ENSG00000185624 P4HB prostate glandular cells High Enhanced P07237 +ENSG00000185624 P4HB seminal vesicle glandular cells High Enhanced P07237 +ENSG00000185624 P4HB testis cells in seminiferous ducts Low Enhanced P07237 +ENSG00000185624 P4HB testis Leydig cells Medium Enhanced P07237 +ENSG00000185630 PBX1 epididymis glandular cells Medium Supported P40424 +ENSG00000185630 PBX1 prostate glandular cells Medium Supported P40424 +ENSG00000185630 PBX1 seminal vesicle glandular cells Medium Supported P40424 +ENSG00000185630 PBX1 testis cells in seminiferous ducts Low Supported P40424 +ENSG00000185630 PBX1 testis Leydig cells Medium Supported P40424 +ENSG00000185670 ZBTB3 epididymis glandular cells Medium Enhanced Q9H5J0 +ENSG00000185670 ZBTB3 prostate glandular cells Low Enhanced Q9H5J0 +ENSG00000185670 ZBTB3 seminal vesicle glandular cells High Enhanced Q9H5J0 +ENSG00000185670 ZBTB3 testis cells in seminiferous ducts Medium Enhanced Q9H5J0 +ENSG00000185670 ZBTB3 testis Leydig cells Medium Enhanced Q9H5J0 +ENSG00000185684 EP400NL testis cells in seminiferous ducts High Enhanced NA +ENSG00000185686 PRAME testis elongated or late spermatids High Enhanced H7C2P3 +ENSG00000185686 PRAME testis Leydig cells Low Enhanced H7C2P3 +ENSG00000185686 PRAME testis pachytene spermatocytes High Enhanced H7C2P3 +ENSG00000185686 PRAME testis preleptotene spermatocytes High Enhanced H7C2P3 +ENSG00000185686 PRAME testis round or early spermatids Medium Enhanced H7C2P3 +ENSG00000185686 PRAME testis spermatogonia High Enhanced H7C2P3 +ENSG00000185813 PCYT2 epididymis glandular cells Medium Enhanced Q99447 +ENSG00000185813 PCYT2 prostate glandular cells Medium Enhanced Q99447 +ENSG00000185813 PCYT2 seminal vesicle glandular cells Low Enhanced Q99447 +ENSG00000185813 PCYT2 testis cells in seminiferous ducts High Enhanced Q99447 +ENSG00000185813 PCYT2 testis Leydig cells High Enhanced Q99447 +ENSG00000185825 BCAP31 epididymis glandular cells Medium Enhanced P51572 +ENSG00000185825 BCAP31 prostate glandular cells Medium Enhanced P51572 +ENSG00000185825 BCAP31 seminal vesicle glandular cells Medium Enhanced P51572 +ENSG00000185825 BCAP31 testis cells in seminiferous ducts Medium Enhanced P51572 +ENSG00000185825 BCAP31 testis Leydig cells Medium Enhanced P51572 +ENSG00000185862 EVI2B epididymis glandular cells Medium Enhanced P34910 +ENSG00000185862 EVI2B prostate glandular cells Low Enhanced P34910 +ENSG00000185862 EVI2B seminal vesicle glandular cells Medium Enhanced P34910 +ENSG00000185862 EVI2B testis cells in seminiferous ducts Medium Enhanced P34910 +ENSG00000185863 TMEM210 testis elongated or late spermatids High Enhanced A6NLX4 +ENSG00000185863 TMEM210 testis Leydig cells Low Enhanced A6NLX4 +ENSG00000185863 TMEM210 testis round or early spermatids High Enhanced A6NLX4 +ENSG00000185880 TRIM69 testis cells in seminiferous ducts High Enhanced NA +ENSG00000185885 IFITM1 epididymis glandular cells High Enhanced P13164 +ENSG00000185888 PRSS38 testis Leydig cells High Enhanced A1L453 +ENSG00000185896 LAMP1 epididymis glandular cells High Enhanced P11279 +ENSG00000185896 LAMP1 prostate glandular cells High Enhanced P11279 +ENSG00000185896 LAMP1 seminal vesicle glandular cells High Enhanced P11279 +ENSG00000185896 LAMP1 testis cells in seminiferous ducts High Enhanced P11279 +ENSG00000185896 LAMP1 testis Leydig cells High Enhanced P11279 +ENSG00000185909 KLHDC8B epididymis glandular cells Medium Supported Q8IXV7 +ENSG00000185909 KLHDC8B seminal vesicle glandular cells Medium Supported Q8IXV7 +ENSG00000185909 KLHDC8B testis cells in seminiferous ducts Medium Supported Q8IXV7 +ENSG00000185909 KLHDC8B testis Leydig cells Medium Supported Q8IXV7 +ENSG00000185955 C7orf61 testis elongated or late spermatids High Enhanced Q8IZ16 +ENSG00000185955 C7orf61 testis round or early spermatids High Enhanced Q8IZ16 +ENSG00000185963 BICD2 epididymis glandular cells Low Enhanced Q8TD16 +ENSG00000185963 BICD2 seminal vesicle glandular cells Low Enhanced Q8TD16 +ENSG00000185963 BICD2 testis cells in seminiferous ducts Medium Enhanced Q8TD16 +ENSG00000185963 BICD2 testis Leydig cells Medium Enhanced Q8TD16 +ENSG00000185988 PLK5 testis preleptotene spermatocytes Medium Enhanced Q496M5 +ENSG00000185988 PLK5 testis spermatogonia High Enhanced Q496M5 +ENSG00000186010 NDUFA13 prostate glandular cells High Supported Q9P0J0 +ENSG00000186010 NDUFA13 seminal vesicle glandular cells High Supported Q9P0J0 +ENSG00000186010 NDUFA13 testis cells in seminiferous ducts Medium Supported Q9P0J0 +ENSG00000186010 NDUFA13 testis Leydig cells High Supported Q9P0J0 +ENSG00000186075 ZPBP2 testis elongated or late spermatids High Enhanced Q6X784 +ENSG00000186075 ZPBP2 testis pachytene spermatocytes High Enhanced Q6X784 +ENSG00000186075 ZPBP2 testis preleptotene spermatocytes Low Enhanced Q6X784 +ENSG00000186075 ZPBP2 testis round or early spermatids High Enhanced Q6X784 +ENSG00000186075 ZPBP2 testis spermatogonia Low Enhanced Q6X784 +ENSG00000186081 KRT5 epididymis glandular cells High Enhanced P13647 +ENSG00000186081 KRT5 prostate glandular cells High Enhanced P13647 +ENSG00000186081 KRT5 seminal vesicle glandular cells High Enhanced P13647 +ENSG00000186115 CYP4F2 epididymis glandular cells Low Supported P78329 +ENSG00000186115 CYP4F2 seminal vesicle glandular cells Low Supported P78329 +ENSG00000186150 UBL4B testis cells in seminiferous ducts Medium Enhanced Q8N7F7 +ENSG00000186150 UBL4B testis Leydig cells Medium Enhanced Q8N7F7 +ENSG00000186185 KIF18B testis cells in seminiferous ducts Low Enhanced Q86Y91 +ENSG00000186198 SLC51B testis cells in seminiferous ducts Low Enhanced Q86UW2 +ENSG00000186260 MKL2 epididymis glandular cells High Supported Q9ULH7 +ENSG00000186260 MKL2 prostate glandular cells Medium Supported Q9ULH7 +ENSG00000186260 MKL2 seminal vesicle glandular cells High Supported Q9ULH7 +ENSG00000186260 MKL2 testis cells in seminiferous ducts High Supported Q9ULH7 +ENSG00000186260 MKL2 testis Leydig cells High Supported Q9ULH7 +ENSG00000186335 SLC36A2 testis cells in seminiferous ducts Low Enhanced Q495M3 +ENSG00000186350 RXRA epididymis glandular cells Medium Supported P19793 +ENSG00000186350 RXRA prostate glandular cells High Supported P19793 +ENSG00000186350 RXRA seminal vesicle glandular cells Medium Supported P19793 +ENSG00000186350 RXRA testis cells in seminiferous ducts Medium Supported P19793 +ENSG00000186350 RXRA testis Leydig cells Medium Supported P19793 +ENSG00000186364 NUDT17 epididymis glandular cells High Enhanced P0C025 +ENSG00000186364 NUDT17 prostate glandular cells Medium Enhanced P0C025 +ENSG00000186364 NUDT17 seminal vesicle glandular cells Medium Enhanced P0C025 +ENSG00000186364 NUDT17 testis cells in seminiferous ducts High Enhanced P0C025 +ENSG00000186364 NUDT17 testis Leydig cells Medium Enhanced P0C025 +ENSG00000186376 ZNF75D epididymis glandular cells High Supported P51815 +ENSG00000186376 ZNF75D prostate glandular cells High Supported P51815 +ENSG00000186376 ZNF75D seminal vesicle glandular cells Medium Supported P51815 +ENSG00000186376 ZNF75D testis cells in seminiferous ducts High Supported P51815 +ENSG00000186376 ZNF75D testis Leydig cells Medium Supported P51815 +ENSG00000186432 KPNA4 epididymis glandular cells High Enhanced O00629 +ENSG00000186432 KPNA4 prostate glandular cells Medium Enhanced O00629 +ENSG00000186432 KPNA4 seminal vesicle glandular cells Medium Enhanced O00629 +ENSG00000186432 KPNA4 testis cells in seminiferous ducts High Enhanced O00629 +ENSG00000186432 KPNA4 testis Leydig cells High Enhanced O00629 +ENSG00000186471 AKAP14 testis elongated or late spermatids High Enhanced Q86UN6 +ENSG00000186471 AKAP14 testis pachytene spermatocytes Medium Enhanced Q86UN6 +ENSG00000186471 AKAP14 testis preleptotene spermatocytes Medium Enhanced Q86UN6 +ENSG00000186471 AKAP14 testis round or early spermatids Medium Enhanced Q86UN6 +ENSG00000186471 AKAP14 testis sertoli cells Medium Enhanced Q86UN6 +ENSG00000186522 SEPT10 epididymis glandular cells Medium Enhanced Q9P0V9 +ENSG00000186522 SEPT10 prostate glandular cells Medium Enhanced Q9P0V9 +ENSG00000186522 SEPT10 seminal vesicle glandular cells Medium Enhanced Q9P0V9 +ENSG00000186522 SEPT10 testis cells in seminiferous ducts High Enhanced Q9P0V9 +ENSG00000186522 SEPT10 testis Leydig cells Medium Enhanced Q9P0V9 +ENSG00000186575 NF2 epididymis glandular cells High Supported P35240 +ENSG00000186575 NF2 prostate glandular cells Medium Supported P35240 +ENSG00000186575 NF2 seminal vesicle glandular cells High Supported P35240 +ENSG00000186575 NF2 testis cells in seminiferous ducts High Supported P35240 +ENSG00000186575 NF2 testis Leydig cells Medium Supported P35240 +ENSG00000186579 DEFB106A epididymis glandular cells High Supported NA +ENSG00000186834 HEXIM1 epididymis glandular cells High Supported O94992 +ENSG00000186834 HEXIM1 prostate glandular cells High Supported O94992 +ENSG00000186834 HEXIM1 seminal vesicle glandular cells High Supported O94992 +ENSG00000186834 HEXIM1 testis cells in seminiferous ducts High Supported O94992 +ENSG00000186834 HEXIM1 testis Leydig cells High Supported O94992 +ENSG00000186847 KRT14 prostate glandular cells Medium Enhanced P02533 +ENSG00000186868 MAPT testis cells in seminiferous ducts Low Enhanced NA +ENSG00000186951 PPARA epididymis glandular cells Medium Supported Q07869 +ENSG00000186951 PPARA prostate glandular cells Medium Supported Q07869 +ENSG00000186951 PPARA seminal vesicle glandular cells Medium Supported Q07869 +ENSG00000186951 PPARA testis cells in seminiferous ducts High Supported Q07869 +ENSG00000186951 PPARA testis Leydig cells High Supported Q07869 +ENSG00000187003 ACTL7A testis elongated or late spermatids High Enhanced Q9Y615 +ENSG00000187003 ACTL7A testis round or early spermatids High Enhanced Q9Y615 +ENSG00000187017 ESPN epididymis glandular cells High Enhanced B1AK53 +ENSG00000187017 ESPN testis sertoli cells High Enhanced B1AK53 +ENSG00000187082 DEFB106B epididymis glandular cells High Supported NA +ENSG00000187097 ENTPD5 epididymis glandular cells Low Enhanced O75356 +ENSG00000187097 ENTPD5 prostate glandular cells High Enhanced O75356 +ENSG00000187097 ENTPD5 seminal vesicle glandular cells Low Enhanced O75356 +ENSG00000187097 ENTPD5 testis cells in seminiferous ducts Low Enhanced O75356 +ENSG00000187097 ENTPD5 testis Leydig cells Low Enhanced O75356 +ENSG00000187098 MITF epididymis glandular cells Low Enhanced O75030 +ENSG00000187164 SHTN1 epididymis glandular cells Low Enhanced A0MZ66 +ENSG00000187164 SHTN1 testis cells in seminiferous ducts Medium Enhanced A0MZ66 +ENSG00000187186 RP11-195F19.5 testis elongated or late spermatids High Enhanced B7Z3J9 +ENSG00000187186 RP11-195F19.5 testis preleptotene spermatocytes Low Enhanced B7Z3J9 +ENSG00000187186 RP11-195F19.5 testis round or early spermatids High Enhanced B7Z3J9 +ENSG00000187186 RP11-195F19.5 testis sertoli cells High Enhanced B7Z3J9 +ENSG00000187239 FNBP1 epididymis glandular cells Low Enhanced Q96RU3 +ENSG00000187239 FNBP1 testis cells in seminiferous ducts Low Enhanced Q96RU3 +ENSG00000187239 FNBP1 testis Leydig cells Low Enhanced Q96RU3 +ENSG00000187475 HIST1H1T testis cells in seminiferous ducts High Enhanced P22492 +ENSG00000187492 CDHR4 testis cells in seminiferous ducts Medium Enhanced A6H8M9 +ENSG00000187516 HYPM testis cells in seminiferous ducts Low Supported O75409 +ENSG00000187531 SIRT7 epididymis glandular cells Medium Enhanced Q9NRC8 +ENSG00000187531 SIRT7 seminal vesicle glandular cells Medium Enhanced Q9NRC8 +ENSG00000187531 SIRT7 testis cells in seminiferous ducts Medium Enhanced Q9NRC8 +ENSG00000187531 SIRT7 testis Leydig cells Medium Enhanced Q9NRC8 +ENSG00000187556 NANOS3 testis cells in seminiferous ducts Medium Enhanced P60323 +ENSG00000187678 SPRY4 epididymis glandular cells Medium Enhanced Q9C004 +ENSG00000187678 SPRY4 prostate glandular cells Medium Enhanced Q9C004 +ENSG00000187678 SPRY4 seminal vesicle glandular cells Medium Enhanced Q9C004 +ENSG00000187678 SPRY4 testis cells in seminiferous ducts Medium Enhanced Q9C004 +ENSG00000187678 SPRY4 testis Leydig cells Medium Enhanced Q9C004 +ENSG00000187690 CXorf67 testis pachytene spermatocytes High Enhanced Q86X51 +ENSG00000187690 CXorf67 testis preleptotene spermatocytes High Enhanced Q86X51 +ENSG00000187690 CXorf67 testis round or early spermatids Medium Enhanced Q86X51 +ENSG00000187690 CXorf67 testis spermatogonia High Enhanced Q86X51 +ENSG00000187726 DNAJB13 testis elongated or late spermatids High Enhanced P59910 +ENSG00000187726 DNAJB13 testis Leydig cells Low Enhanced P59910 +ENSG00000187726 DNAJB13 testis pachytene spermatocytes Medium Enhanced P59910 +ENSG00000187726 DNAJB13 testis round or early spermatids Medium Enhanced P59910 +ENSG00000187773 FAM69C testis elongated or late spermatids High Enhanced Q0P6D2 +ENSG00000187773 FAM69C testis round or early spermatids High Enhanced Q0P6D2 +ENSG00000187775 DNAH17 testis cells in seminiferous ducts Low Enhanced Q9UFH2 +ENSG00000187778 MCRS1 epididymis glandular cells High Supported Q96EZ8 +ENSG00000187778 MCRS1 prostate glandular cells High Supported Q96EZ8 +ENSG00000187778 MCRS1 seminal vesicle glandular cells High Supported Q96EZ8 +ENSG00000187778 MCRS1 testis cells in seminiferous ducts High Supported Q96EZ8 +ENSG00000187778 MCRS1 testis Leydig cells Medium Supported Q96EZ8 +ENSG00000187796 CARD9 epididymis glandular cells Low Enhanced Q9H257 +ENSG00000187796 CARD9 testis cells in seminiferous ducts Low Enhanced Q9H257 +ENSG00000187837 HIST1H1C epididymis glandular cells High Supported P16403 +ENSG00000187837 HIST1H1C prostate glandular cells High Supported P16403 +ENSG00000187837 HIST1H1C seminal vesicle glandular cells High Supported P16403 +ENSG00000187837 HIST1H1C testis cells in seminiferous ducts High Supported P16403 +ENSG00000187837 HIST1H1C testis Leydig cells High Supported P16403 +ENSG00000187838 PLSCR3 epididymis glandular cells Medium Supported Q8WYZ0 +ENSG00000187838 PLSCR3 prostate glandular cells Medium Supported Q8WYZ0 +ENSG00000187838 PLSCR3 seminal vesicle glandular cells High Supported Q8WYZ0 +ENSG00000187838 PLSCR3 testis cells in seminiferous ducts Medium Supported Q8WYZ0 +ENSG00000187838 PLSCR3 testis Leydig cells High Supported Q8WYZ0 +ENSG00000187840 EIF4EBP1 epididymis glandular cells Low Supported Q13541 +ENSG00000187840 EIF4EBP1 prostate glandular cells Medium Supported Q13541 +ENSG00000187840 EIF4EBP1 seminal vesicle glandular cells Medium Supported Q13541 +ENSG00000187840 EIF4EBP1 testis cells in seminiferous ducts Low Supported Q13541 +ENSG00000187840 EIF4EBP1 testis Leydig cells Medium Supported Q13541 +ENSG00000187867 PALM3 epididymis glandular cells High Enhanced A6NDB9 +ENSG00000187867 PALM3 seminal vesicle glandular cells High Enhanced A6NDB9 +ENSG00000187867 PALM3 testis cells in seminiferous ducts Medium Enhanced A6NDB9 +ENSG00000187867 PALM3 testis Leydig cells Low Enhanced A6NDB9 +ENSG00000187969 ZCCHC13 testis elongated or late spermatids High Enhanced Q8WW36 +ENSG00000187969 ZCCHC13 testis Leydig cells Low Enhanced Q8WW36 +ENSG00000187969 ZCCHC13 testis round or early spermatids Low Enhanced Q8WW36 +ENSG00000188021 UBQLN2 epididymis glandular cells Medium Enhanced Q9UHD9 +ENSG00000188021 UBQLN2 prostate glandular cells High Enhanced Q9UHD9 +ENSG00000188021 UBQLN2 testis cells in seminiferous ducts Medium Enhanced Q9UHD9 +ENSG00000188021 UBQLN2 testis Leydig cells Medium Enhanced Q9UHD9 +ENSG00000188112 C6orf132 testis cells in seminiferous ducts Low Enhanced Q5T0Z8 +ENSG00000188112 C6orf132 testis Leydig cells Low Enhanced Q5T0Z8 +ENSG00000188120 DAZ1 testis pachytene spermatocytes Medium Supported Q9NQZ3 +ENSG00000188120 DAZ1 testis preleptotene spermatocytes High Supported Q9NQZ3 +ENSG00000188120 DAZ1 testis spermatogonia High Supported Q9NQZ3 +ENSG00000188130 MAPK12 prostate glandular cells Low Enhanced P53778 +ENSG00000188130 MAPK12 testis cells in seminiferous ducts Low Enhanced P53778 +ENSG00000188130 MAPK12 testis Leydig cells Low Enhanced P53778 +ENSG00000188163 FAM166A epididymis glandular cells Low Enhanced Q6J272 +ENSG00000188163 FAM166A testis elongated or late spermatids High Enhanced Q6J272 +ENSG00000188163 FAM166A testis Leydig cells Low Enhanced Q6J272 +ENSG00000188163 FAM166A testis pachytene spermatocytes Low Enhanced Q6J272 +ENSG00000188163 FAM166A testis preleptotene spermatocytes Medium Enhanced Q6J272 +ENSG00000188163 FAM166A testis round or early spermatids Medium Enhanced Q6J272 +ENSG00000188163 FAM166A testis spermatogonia Medium Enhanced Q6J272 +ENSG00000188186 LAMTOR4 epididymis glandular cells High Enhanced Q0VGL1 +ENSG00000188186 LAMTOR4 prostate glandular cells High Enhanced Q0VGL1 +ENSG00000188186 LAMTOR4 seminal vesicle glandular cells Medium Enhanced Q0VGL1 +ENSG00000188186 LAMTOR4 testis cells in seminiferous ducts Low Enhanced Q0VGL1 +ENSG00000188186 LAMTOR4 testis Leydig cells Medium Enhanced Q0VGL1 +ENSG00000188229 TUBB4B epididymis glandular cells High Enhanced P68371 +ENSG00000188229 TUBB4B prostate glandular cells Medium Enhanced P68371 +ENSG00000188229 TUBB4B seminal vesicle glandular cells Medium Enhanced P68371 +ENSG00000188229 TUBB4B testis cells in seminiferous ducts High Enhanced P68371 +ENSG00000188229 TUBB4B testis Leydig cells Medium Enhanced P68371 +ENSG00000188257 PLA2G2A prostate glandular cells Medium Enhanced P14555 +ENSG00000188334 BSPH1 epididymis glandular cells High Enhanced Q075Z2 +ENSG00000188342 GTF2F2 epididymis glandular cells High Supported P13984 +ENSG00000188342 GTF2F2 prostate glandular cells Low Supported P13984 +ENSG00000188342 GTF2F2 seminal vesicle glandular cells Low Supported P13984 +ENSG00000188342 GTF2F2 testis cells in seminiferous ducts High Supported P13984 +ENSG00000188342 GTF2F2 testis Leydig cells Medium Supported P13984 +ENSG00000188343 FAM92A testis cells in seminiferous ducts High Enhanced A1XBS5 +ENSG00000188375 H3F3C epididymis glandular cells High Supported Q6NXT2 +ENSG00000188375 H3F3C prostate glandular cells High Supported Q6NXT2 +ENSG00000188375 H3F3C seminal vesicle glandular cells High Supported Q6NXT2 +ENSG00000188375 H3F3C testis cells in seminiferous ducts High Supported Q6NXT2 +ENSG00000188375 H3F3C testis Leydig cells High Supported Q6NXT2 +ENSG00000188389 PDCD1 testis cells in seminiferous ducts Low Enhanced NA +ENSG00000188486 H2AFX epididymis glandular cells Medium Supported P16104 +ENSG00000188486 H2AFX prostate glandular cells Medium Supported P16104 +ENSG00000188486 H2AFX seminal vesicle glandular cells Medium Supported P16104 +ENSG00000188486 H2AFX testis cells in seminiferous ducts High Supported P16104 +ENSG00000188486 H2AFX testis Leydig cells Medium Supported P16104 +ENSG00000188522 FAM83G epididymis glandular cells Medium Enhanced A6ND36 +ENSG00000188522 FAM83G prostate glandular cells Low Enhanced A6ND36 +ENSG00000188522 FAM83G seminal vesicle glandular cells Medium Enhanced A6ND36 +ENSG00000188522 FAM83G testis Leydig cells Low Enhanced A6ND36 +ENSG00000188523 CFAP77 testis cells in seminiferous ducts Medium Enhanced Q6ZQR2 +ENSG00000188596 CFAP54 testis cells in seminiferous ducts Low Enhanced Q96N23 +ENSG00000188612 SUMO2 epididymis glandular cells High Enhanced P61956 +ENSG00000188612 SUMO2 prostate glandular cells High Enhanced P61956 +ENSG00000188612 SUMO2 seminal vesicle glandular cells High Enhanced P61956 +ENSG00000188612 SUMO2 testis cells in seminiferous ducts High Enhanced P61956 +ENSG00000188612 SUMO2 testis Leydig cells Medium Enhanced P61956 +ENSG00000188643 S100A16 testis Leydig cells Medium Enhanced Q96FQ6 +ENSG00000188649 CC2D2B testis cells in seminiferous ducts Medium Enhanced Q6DHV5 +ENSG00000188649 CC2D2B testis Leydig cells Low Enhanced Q6DHV5 +ENSG00000188659 SAXO2 epididymis glandular cells Low Enhanced Q658L1 +ENSG00000188732 FAM221A epididymis glandular cells Medium Enhanced A4D161 +ENSG00000188732 FAM221A prostate glandular cells Medium Enhanced A4D161 +ENSG00000188732 FAM221A seminal vesicle glandular cells Medium Enhanced A4D161 +ENSG00000188732 FAM221A testis cells in seminiferous ducts High Enhanced A4D161 +ENSG00000188732 FAM221A testis Leydig cells High Enhanced A4D161 +ENSG00000188782 CATSPER4 testis elongated or late spermatids High Enhanced Q7RTX7 +ENSG00000188986 NELFB epididymis glandular cells High Enhanced Q8WX92 +ENSG00000188986 NELFB prostate glandular cells Medium Enhanced Q8WX92 +ENSG00000188986 NELFB seminal vesicle glandular cells Medium Enhanced Q8WX92 +ENSG00000188986 NELFB testis cells in seminiferous ducts High Enhanced Q8WX92 +ENSG00000188986 NELFB testis Leydig cells Medium Enhanced Q8WX92 +ENSG00000189058 APOD testis Leydig cells High Enhanced P05090 +ENSG00000189060 H1F0 epididymis glandular cells Medium Enhanced P07305 +ENSG00000189060 H1F0 prostate glandular cells High Enhanced P07305 +ENSG00000189060 H1F0 seminal vesicle glandular cells High Enhanced P07305 +ENSG00000189060 H1F0 testis cells in seminiferous ducts High Enhanced P07305 +ENSG00000189060 H1F0 testis Leydig cells High Enhanced P07305 +ENSG00000189064 GAGE2A testis cells in seminiferous ducts High Supported Q6NT46 +ENSG00000189064 GAGE2A testis pachytene spermatocytes Low Supported Q6NT46 +ENSG00000189064 GAGE2A testis preleptotene spermatocytes High Supported Q6NT46 +ENSG00000189064 GAGE2A testis spermatogonia High Supported Q6NT46 +ENSG00000189091 SF3B3 epididymis glandular cells High Supported Q15393 +ENSG00000189091 SF3B3 prostate glandular cells High Supported Q15393 +ENSG00000189091 SF3B3 seminal vesicle glandular cells High Supported Q15393 +ENSG00000189091 SF3B3 testis cells in seminiferous ducts High Supported Q15393 +ENSG00000189091 SF3B3 testis Leydig cells High Supported Q15393 +ENSG00000189139 FSCB testis elongated or late spermatids High Supported Q5H9T9 +ENSG00000189139 FSCB testis pachytene spermatocytes High Supported Q5H9T9 +ENSG00000189139 FSCB testis round or early spermatids High Supported Q5H9T9 +ENSG00000189143 CLDN4 epididymis glandular cells Medium Enhanced O14493 +ENSG00000189143 CLDN4 prostate glandular cells Medium Enhanced O14493 +ENSG00000189143 CLDN4 seminal vesicle glandular cells Medium Enhanced O14493 +ENSG00000189221 MAOA epididymis glandular cells Medium Enhanced P21397 +ENSG00000189221 MAOA prostate glandular cells High Enhanced P21397 +ENSG00000189221 MAOA seminal vesicle glandular cells High Enhanced P21397 +ENSG00000189221 MAOA testis Leydig cells Medium Enhanced P21397 +ENSG00000189283 FHIT epididymis glandular cells Medium Enhanced P49789 +ENSG00000189283 FHIT prostate glandular cells Medium Enhanced P49789 +ENSG00000189283 FHIT seminal vesicle glandular cells Medium Enhanced P49789 +ENSG00000189283 FHIT testis cells in seminiferous ducts Medium Enhanced P49789 +ENSG00000189283 FHIT testis Leydig cells Medium Enhanced P49789 +ENSG00000189401 OTUD6A testis cells in seminiferous ducts High Enhanced Q7L8S5 +ENSG00000189403 HMGB1 epididymis glandular cells High Supported P09429 +ENSG00000189403 HMGB1 prostate glandular cells High Supported P09429 +ENSG00000189403 HMGB1 seminal vesicle glandular cells Low Supported P09429 +ENSG00000189403 HMGB1 testis cells in seminiferous ducts High Supported P09429 +ENSG00000189403 HMGB1 testis Leydig cells Medium Supported P09429 +ENSG00000196136 SERPINA3 prostate glandular cells Medium Enhanced P01011 +ENSG00000196136 SERPINA3 testis cells in seminiferous ducts Low Enhanced P01011 +ENSG00000196136 SERPINA3 testis Leydig cells Medium Enhanced P01011 +ENSG00000196139 AKR1C3 epididymis glandular cells Low Enhanced P42330 +ENSG00000196139 AKR1C3 testis Leydig cells Low Enhanced P42330 +ENSG00000196177 ACADSB prostate glandular cells Low Enhanced P45954 +ENSG00000196177 ACADSB seminal vesicle glandular cells Medium Enhanced P45954 +ENSG00000196177 ACADSB testis cells in seminiferous ducts Low Enhanced P45954 +ENSG00000196177 ACADSB testis Leydig cells Medium Enhanced P45954 +ENSG00000196199 MPHOSPH8 epididymis glandular cells High Enhanced Q99549 +ENSG00000196199 MPHOSPH8 prostate glandular cells Medium Enhanced Q99549 +ENSG00000196199 MPHOSPH8 seminal vesicle glandular cells Medium Enhanced Q99549 +ENSG00000196199 MPHOSPH8 testis cells in seminiferous ducts High Enhanced Q99549 +ENSG00000196199 MPHOSPH8 testis Leydig cells High Enhanced Q99549 +ENSG00000196230 TUBB epididymis glandular cells High Enhanced NA +ENSG00000196230 TUBB prostate glandular cells Medium Enhanced NA +ENSG00000196230 TUBB seminal vesicle glandular cells Medium Enhanced NA +ENSG00000196230 TUBB testis cells in seminiferous ducts High Enhanced NA +ENSG00000196230 TUBB testis Leydig cells Medium Enhanced NA +ENSG00000196235 SUPT5H epididymis glandular cells Medium Enhanced O00267 +ENSG00000196235 SUPT5H prostate glandular cells Medium Enhanced O00267 +ENSG00000196235 SUPT5H seminal vesicle glandular cells Medium Enhanced O00267 +ENSG00000196235 SUPT5H testis cells in seminiferous ducts High Enhanced O00267 +ENSG00000196235 SUPT5H testis Leydig cells Medium Enhanced O00267 +ENSG00000196236 XPNPEP3 epididymis glandular cells High Enhanced Q9NQH7 +ENSG00000196236 XPNPEP3 prostate glandular cells Medium Enhanced Q9NQH7 +ENSG00000196236 XPNPEP3 seminal vesicle glandular cells High Enhanced Q9NQH7 +ENSG00000196236 XPNPEP3 testis cells in seminiferous ducts Medium Enhanced Q9NQH7 +ENSG00000196236 XPNPEP3 testis Leydig cells High Enhanced Q9NQH7 +ENSG00000196284 SUPT3H epididymis glandular cells Medium Enhanced O75486 +ENSG00000196284 SUPT3H prostate glandular cells Medium Enhanced O75486 +ENSG00000196284 SUPT3H seminal vesicle glandular cells Low Enhanced O75486 +ENSG00000196284 SUPT3H testis cells in seminiferous ducts Medium Enhanced O75486 +ENSG00000196284 SUPT3H testis Leydig cells Low Enhanced O75486 +ENSG00000196290 NIF3L1 epididymis glandular cells Medium Enhanced Q9GZT8 +ENSG00000196290 NIF3L1 prostate glandular cells High Enhanced Q9GZT8 +ENSG00000196290 NIF3L1 seminal vesicle glandular cells High Enhanced Q9GZT8 +ENSG00000196290 NIF3L1 testis cells in seminiferous ducts High Enhanced Q9GZT8 +ENSG00000196290 NIF3L1 testis Leydig cells High Enhanced Q9GZT8 +ENSG00000196335 STK31 testis elongated or late spermatids Low Enhanced Q9BXU1 +ENSG00000196335 STK31 testis Leydig cells Low Enhanced Q9BXU1 +ENSG00000196335 STK31 testis pachytene spermatocytes High Enhanced Q9BXU1 +ENSG00000196335 STK31 testis preleptotene spermatocytes Medium Enhanced Q9BXU1 +ENSG00000196335 STK31 testis round or early spermatids High Enhanced Q9BXU1 +ENSG00000196335 STK31 testis spermatogonia Medium Enhanced Q9BXU1 +ENSG00000196352 CD55 testis cells in seminiferous ducts Low Enhanced P08174 +ENSG00000196353 CPNE4 prostate glandular cells High Enhanced Q96A23 +ENSG00000196365 LONP1 epididymis glandular cells High Supported P36776 +ENSG00000196365 LONP1 prostate glandular cells Medium Supported P36776 +ENSG00000196365 LONP1 seminal vesicle glandular cells High Supported P36776 +ENSG00000196365 LONP1 testis cells in seminiferous ducts Medium Supported P36776 +ENSG00000196365 LONP1 testis Leydig cells Medium Supported P36776 +ENSG00000196396 PTPN1 epididymis glandular cells Medium Enhanced P18031 +ENSG00000196396 PTPN1 testis cells in seminiferous ducts Medium Enhanced P18031 +ENSG00000196396 PTPN1 testis Leydig cells Medium Enhanced P18031 +ENSG00000196406 SPANXD testis cells in seminiferous ducts Medium Supported Q9BXN6 +ENSG00000196408 NOXO1 epididymis glandular cells Low Enhanced Q8NFA2 +ENSG00000196408 NOXO1 testis cells in seminiferous ducts Low Enhanced Q8NFA2 +ENSG00000196408 NOXO1 testis Leydig cells Low Enhanced Q8NFA2 +ENSG00000196419 XRCC6 epididymis glandular cells High Enhanced P12956 +ENSG00000196419 XRCC6 prostate glandular cells High Enhanced P12956 +ENSG00000196419 XRCC6 seminal vesicle glandular cells High Enhanced P12956 +ENSG00000196419 XRCC6 testis cells in seminiferous ducts High Enhanced P12956 +ENSG00000196419 XRCC6 testis Leydig cells High Enhanced P12956 +ENSG00000196436 NPIPB15 epididymis glandular cells High Supported A6NHN6 +ENSG00000196436 NPIPB15 prostate glandular cells High Supported A6NHN6 +ENSG00000196436 NPIPB15 seminal vesicle glandular cells High Supported A6NHN6 +ENSG00000196436 NPIPB15 testis elongated or late spermatids High Supported A6NHN6 +ENSG00000196436 NPIPB15 testis Leydig cells High Supported A6NHN6 +ENSG00000196436 NPIPB15 testis peritubular cells High Supported A6NHN6 +ENSG00000196436 NPIPB15 testis preleptotene spermatocytes Low Supported A6NHN6 +ENSG00000196436 NPIPB15 testis round or early spermatids High Supported A6NHN6 +ENSG00000196436 NPIPB15 testis sertoli cells High Supported A6NHN6 +ENSG00000196436 NPIPB15 testis spermatogonia Medium Supported A6NHN6 +ENSG00000196465 MYL6B epididymis glandular cells Low Enhanced P14649 +ENSG00000196465 MYL6B prostate glandular cells Low Enhanced P14649 +ENSG00000196465 MYL6B seminal vesicle glandular cells Low Enhanced P14649 +ENSG00000196465 MYL6B testis Leydig cells Low Enhanced P14649 +ENSG00000196466 ZNF799 epididymis glandular cells Low Supported Q96GE5 +ENSG00000196466 ZNF799 prostate glandular cells Medium Supported Q96GE5 +ENSG00000196466 ZNF799 seminal vesicle glandular cells Medium Supported Q96GE5 +ENSG00000196466 ZNF799 testis cells in seminiferous ducts Medium Supported Q96GE5 +ENSG00000196466 ZNF799 testis Leydig cells Medium Supported Q96GE5 +ENSG00000196470 SIAH1 epididymis glandular cells Medium Enhanced Q8IUQ4 +ENSG00000196470 SIAH1 prostate glandular cells Medium Enhanced Q8IUQ4 +ENSG00000196470 SIAH1 seminal vesicle glandular cells Low Enhanced Q8IUQ4 +ENSG00000196470 SIAH1 testis cells in seminiferous ducts Medium Enhanced Q8IUQ4 +ENSG00000196470 SIAH1 testis Leydig cells Medium Enhanced Q8IUQ4 +ENSG00000196502 SULT1A1 seminal vesicle glandular cells Low Supported P50225 +ENSG00000196502 SULT1A1 testis Leydig cells Low Supported P50225 +ENSG00000196503 ARL9 testis elongated or late spermatids High Enhanced Q6T311 +ENSG00000196526 AFAP1 epididymis glandular cells Medium Enhanced Q8N556 +ENSG00000196526 AFAP1 prostate glandular cells Medium Enhanced Q8N556 +ENSG00000196526 AFAP1 seminal vesicle glandular cells Medium Enhanced Q8N556 +ENSG00000196526 AFAP1 testis cells in seminiferous ducts Medium Enhanced Q8N556 +ENSG00000196526 AFAP1 testis Leydig cells Medium Enhanced Q8N556 +ENSG00000196535 MYO18A epididymis glandular cells High Enhanced Q92614 +ENSG00000196535 MYO18A prostate glandular cells Medium Enhanced Q92614 +ENSG00000196535 MYO18A seminal vesicle glandular cells Low Enhanced Q92614 +ENSG00000196535 MYO18A testis cells in seminiferous ducts High Enhanced Q92614 +ENSG00000196535 MYO18A testis Leydig cells Low Enhanced Q92614 +ENSG00000196549 MME epididymis glandular cells Medium Enhanced P08473 +ENSG00000196549 MME prostate glandular cells High Enhanced P08473 +ENSG00000196549 MME seminal vesicle glandular cells Medium Enhanced P08473 +ENSG00000196569 LAMA2 testis cells in seminiferous ducts Low Enhanced P24043 +ENSG00000196569 LAMA2 testis Leydig cells Low Enhanced P24043 +ENSG00000196586 MYO6 epididymis glandular cells High Enhanced Q9UM54 +ENSG00000196586 MYO6 prostate glandular cells Medium Enhanced Q9UM54 +ENSG00000196586 MYO6 seminal vesicle glandular cells High Enhanced Q9UM54 +ENSG00000196586 MYO6 testis cells in seminiferous ducts High Enhanced Q9UM54 +ENSG00000196586 MYO6 testis Leydig cells Medium Enhanced Q9UM54 +ENSG00000196591 HDAC2 epididymis glandular cells High Supported Q92769 +ENSG00000196591 HDAC2 prostate glandular cells High Supported Q92769 +ENSG00000196591 HDAC2 seminal vesicle glandular cells Medium Supported Q92769 +ENSG00000196591 HDAC2 testis cells in seminiferous ducts High Supported Q92769 +ENSG00000196591 HDAC2 testis Leydig cells High Supported Q92769 +ENSG00000196616 ADH1B epididymis glandular cells Low Supported P00325 +ENSG00000196616 ADH1B seminal vesicle glandular cells Low Supported P00325 +ENSG00000196659 TTC30B epididymis glandular cells Medium Supported Q8N4P2 +ENSG00000196659 TTC30B testis cells in seminiferous ducts High Supported Q8N4P2 +ENSG00000196660 SLC30A10 testis Leydig cells Low Enhanced Q6XR72 +ENSG00000196663 TECPR2 epididymis glandular cells High Enhanced O15040 +ENSG00000196663 TECPR2 prostate glandular cells Medium Enhanced O15040 +ENSG00000196663 TECPR2 seminal vesicle glandular cells Medium Enhanced O15040 +ENSG00000196663 TECPR2 testis cells in seminiferous ducts High Enhanced O15040 +ENSG00000196735 HLA-DQA1 epididymis glandular cells Low Enhanced E9PI37 +ENSG00000196735 HLA-DQA1 testis Leydig cells Low Enhanced E9PI37 +ENSG00000196743 GM2A epididymis glandular cells High Enhanced P17900 +ENSG00000196743 GM2A prostate glandular cells High Enhanced P17900 +ENSG00000196743 GM2A seminal vesicle glandular cells High Enhanced P17900 +ENSG00000196743 GM2A testis cells in seminiferous ducts Medium Enhanced P17900 +ENSG00000196743 GM2A testis Leydig cells High Enhanced P17900 +ENSG00000196747 HIST1H2AI epididymis glandular cells Medium Supported NA +ENSG00000196747 HIST1H2AI prostate glandular cells Low Supported NA +ENSG00000196747 HIST1H2AI seminal vesicle glandular cells Medium Supported NA +ENSG00000196747 HIST1H2AI testis cells in seminiferous ducts High Supported NA +ENSG00000196747 HIST1H2AI testis Leydig cells Low Supported NA +ENSG00000196781 TLE1 epididymis glandular cells High Supported Q04724 +ENSG00000196781 TLE1 prostate glandular cells Medium Supported Q04724 +ENSG00000196781 TLE1 seminal vesicle glandular cells Medium Supported Q04724 +ENSG00000196781 TLE1 testis cells in seminiferous ducts High Supported Q04724 +ENSG00000196781 TLE1 testis Leydig cells Medium Supported Q04724 +ENSG00000196787 HIST1H2AG epididymis glandular cells Medium Supported NA +ENSG00000196787 HIST1H2AG prostate glandular cells Low Supported NA +ENSG00000196787 HIST1H2AG seminal vesicle glandular cells Medium Supported NA +ENSG00000196787 HIST1H2AG testis elongated or late spermatids High Supported NA +ENSG00000196787 HIST1H2AG testis pachytene spermatocytes High Supported NA +ENSG00000196787 HIST1H2AG testis preleptotene spermatocytes High Supported NA +ENSG00000196787 HIST1H2AG testis round or early spermatids High Supported NA +ENSG00000196787 HIST1H2AG testis spermatogonia High Supported NA +ENSG00000196812 ZSCAN16 epididymis glandular cells High Supported Q9H4T2 +ENSG00000196812 ZSCAN16 prostate glandular cells High Supported Q9H4T2 +ENSG00000196812 ZSCAN16 seminal vesicle glandular cells High Supported Q9H4T2 +ENSG00000196812 ZSCAN16 testis cells in seminiferous ducts High Supported Q9H4T2 +ENSG00000196812 ZSCAN16 testis Leydig cells Medium Supported Q9H4T2 +ENSG00000196866 HIST1H2AD epididymis glandular cells Medium Supported P20671 +ENSG00000196866 HIST1H2AD prostate glandular cells Low Supported P20671 +ENSG00000196866 HIST1H2AD seminal vesicle glandular cells Medium Supported P20671 +ENSG00000196866 HIST1H2AD testis cells in seminiferous ducts High Supported P20671 +ENSG00000196866 HIST1H2AD testis Leydig cells Low Supported P20671 +ENSG00000196878 LAMB3 epididymis glandular cells Low Enhanced Q13751 +ENSG00000196878 LAMB3 prostate glandular cells Low Enhanced Q13751 +ENSG00000196878 LAMB3 testis cells in seminiferous ducts Low Enhanced Q13751 +ENSG00000196878 LAMB3 testis Leydig cells Low Enhanced Q13751 +ENSG00000196890 HIST3H2BB epididymis glandular cells High Supported Q8N257 +ENSG00000196890 HIST3H2BB prostate glandular cells High Supported Q8N257 +ENSG00000196890 HIST3H2BB seminal vesicle glandular cells High Supported Q8N257 +ENSG00000196890 HIST3H2BB testis cells in seminiferous ducts High Supported Q8N257 +ENSG00000196890 HIST3H2BB testis Leydig cells High Supported Q8N257 +ENSG00000196911 KPNA5 seminal vesicle glandular cells Low Enhanced O15131 +ENSG00000196911 KPNA5 testis elongated or late spermatids High Enhanced O15131 +ENSG00000196911 KPNA5 testis Leydig cells Low Enhanced O15131 +ENSG00000196911 KPNA5 testis pachytene spermatocytes High Enhanced O15131 +ENSG00000196911 KPNA5 testis round or early spermatids High Enhanced O15131 +ENSG00000196924 FLNA epididymis glandular cells Low Enhanced P21333 +ENSG00000196924 FLNA testis cells in seminiferous ducts Low Enhanced P21333 +ENSG00000196937 FAM3C epididymis glandular cells High Enhanced Q92520 +ENSG00000196937 FAM3C prostate glandular cells Medium Enhanced Q92520 +ENSG00000196937 FAM3C seminal vesicle glandular cells Medium Enhanced Q92520 +ENSG00000196937 FAM3C testis cells in seminiferous ducts Low Enhanced Q92520 +ENSG00000196937 FAM3C testis Leydig cells Medium Enhanced Q92520 +ENSG00000197043 ANXA6 epididymis glandular cells Medium Enhanced P08133 +ENSG00000197043 ANXA6 prostate glandular cells Low Enhanced P08133 +ENSG00000197043 ANXA6 seminal vesicle glandular cells Medium Enhanced P08133 +ENSG00000197043 ANXA6 testis cells in seminiferous ducts High Enhanced P08133 +ENSG00000197043 ANXA6 testis Leydig cells Medium Enhanced P08133 +ENSG00000197061 HIST1H4C epididymis glandular cells Low Supported NA +ENSG00000197061 HIST1H4C prostate glandular cells Low Supported NA +ENSG00000197061 HIST1H4C seminal vesicle glandular cells Medium Supported NA +ENSG00000197061 HIST1H4C testis cells in seminiferous ducts Medium Supported NA +ENSG00000197081 IGF2R epididymis glandular cells Medium Supported P11717 +ENSG00000197081 IGF2R prostate glandular cells Medium Supported P11717 +ENSG00000197081 IGF2R testis cells in seminiferous ducts Medium Supported P11717 +ENSG00000197081 IGF2R testis Leydig cells Medium Supported P11717 +ENSG00000197102 DYNC1H1 epididymis glandular cells Low Enhanced Q14204 +ENSG00000197102 DYNC1H1 seminal vesicle glandular cells Low Enhanced Q14204 +ENSG00000197102 DYNC1H1 testis cells in seminiferous ducts Medium Enhanced Q14204 +ENSG00000197140 ADAM32 testis cells in seminiferous ducts Medium Enhanced E7ER82 +ENSG00000197142 ACSL5 epididymis glandular cells High Enhanced Q9ULC5 +ENSG00000197142 ACSL5 seminal vesicle glandular cells Low Enhanced Q9ULC5 +ENSG00000197142 ACSL5 testis Leydig cells Low Enhanced Q9ULC5 +ENSG00000197153 HIST1H3J epididymis glandular cells High Supported NA +ENSG00000197153 HIST1H3J prostate glandular cells High Supported NA +ENSG00000197153 HIST1H3J seminal vesicle glandular cells High Supported NA +ENSG00000197153 HIST1H3J testis cells in seminiferous ducts High Supported NA +ENSG00000197153 HIST1H3J testis Leydig cells High Supported NA +ENSG00000197157 SND1 epididymis glandular cells Medium Enhanced Q7KZF4 +ENSG00000197157 SND1 prostate glandular cells Medium Enhanced Q7KZF4 +ENSG00000197157 SND1 seminal vesicle glandular cells Medium Enhanced Q7KZF4 +ENSG00000197157 SND1 testis cells in seminiferous ducts Medium Enhanced Q7KZF4 +ENSG00000197157 SND1 testis Leydig cells Medium Enhanced Q7KZF4 +ENSG00000197165 SULT1A2 seminal vesicle glandular cells Low Supported P50226 +ENSG00000197168 NEK5 epididymis glandular cells Low Enhanced Q6P3R8 +ENSG00000197168 NEK5 testis elongated or late spermatids High Enhanced Q6P3R8 +ENSG00000197168 NEK5 testis Leydig cells Low Enhanced Q6P3R8 +ENSG00000197168 NEK5 testis round or early spermatids High Enhanced Q6P3R8 +ENSG00000197170 PSMD12 epididymis glandular cells Low Enhanced O00232 +ENSG00000197170 PSMD12 prostate glandular cells Low Enhanced O00232 +ENSG00000197170 PSMD12 seminal vesicle glandular cells Low Enhanced O00232 +ENSG00000197170 PSMD12 testis cells in seminiferous ducts Medium Enhanced O00232 +ENSG00000197170 PSMD12 testis Leydig cells Medium Enhanced O00232 +ENSG00000197183 NOL4L epididymis glandular cells High Enhanced Q96MY1 +ENSG00000197183 NOL4L prostate glandular cells Low Enhanced Q96MY1 +ENSG00000197183 NOL4L seminal vesicle glandular cells Medium Enhanced Q96MY1 +ENSG00000197183 NOL4L testis Leydig cells Low Enhanced Q96MY1 +ENSG00000197183 NOL4L testis pachytene spermatocytes Low Enhanced Q96MY1 +ENSG00000197183 NOL4L testis round or early spermatids Low Enhanced Q96MY1 +ENSG00000197183 NOL4L testis sertoli cells High Enhanced Q96MY1 +ENSG00000197217 ENTPD4 epididymis glandular cells High Supported Q9Y227 +ENSG00000197217 ENTPD4 prostate glandular cells High Supported Q9Y227 +ENSG00000197217 ENTPD4 seminal vesicle glandular cells High Supported Q9Y227 +ENSG00000197217 ENTPD4 testis cells in seminiferous ducts High Supported Q9Y227 +ENSG00000197217 ENTPD4 testis Leydig cells Medium Supported Q9Y227 +ENSG00000197238 HIST1H4J epididymis glandular cells Low Supported NA +ENSG00000197238 HIST1H4J prostate glandular cells Low Supported NA +ENSG00000197238 HIST1H4J seminal vesicle glandular cells Medium Supported NA +ENSG00000197238 HIST1H4J testis cells in seminiferous ducts Medium Supported NA +ENSG00000197249 SERPINA1 prostate glandular cells Medium Enhanced P01009 +ENSG00000197249 SERPINA1 seminal vesicle glandular cells Low Enhanced P01009 +ENSG00000197249 SERPINA1 testis cells in seminiferous ducts Low Enhanced P01009 +ENSG00000197253 TPSB2 testis Leydig cells Medium Supported P20231 +ENSG00000197283 SYNGAP1 epididymis glandular cells Low Enhanced B7ZCA0 +ENSG00000197283 SYNGAP1 seminal vesicle glandular cells Medium Enhanced B7ZCA0 +ENSG00000197283 SYNGAP1 testis Leydig cells Medium Enhanced B7ZCA0 +ENSG00000197323 TRIM33 epididymis glandular cells Medium Supported Q9UPN9 +ENSG00000197323 TRIM33 prostate glandular cells Medium Supported Q9UPN9 +ENSG00000197323 TRIM33 seminal vesicle glandular cells Low Supported Q9UPN9 +ENSG00000197323 TRIM33 testis cells in seminiferous ducts Medium Supported Q9UPN9 +ENSG00000197323 TRIM33 testis Leydig cells Low Supported Q9UPN9 +ENSG00000197386 HTT epididymis glandular cells Low Enhanced P42858 +ENSG00000197386 HTT prostate glandular cells Low Enhanced P42858 +ENSG00000197386 HTT seminal vesicle glandular cells Medium Enhanced P42858 +ENSG00000197386 HTT testis cells in seminiferous ducts Medium Enhanced P42858 +ENSG00000197386 HTT testis Leydig cells Medium Enhanced P42858 +ENSG00000197408 CYP2B6 epididymis glandular cells Low Supported P20813 +ENSG00000197408 CYP2B6 prostate glandular cells Low Supported P20813 +ENSG00000197408 CYP2B6 seminal vesicle glandular cells Low Supported P20813 +ENSG00000197408 CYP2B6 testis cells in seminiferous ducts Low Supported P20813 +ENSG00000197408 CYP2B6 testis Leydig cells Low Supported P20813 +ENSG00000197409 HIST1H3D epididymis glandular cells High Supported NA +ENSG00000197409 HIST1H3D prostate glandular cells High Supported NA +ENSG00000197409 HIST1H3D seminal vesicle glandular cells High Supported NA +ENSG00000197409 HIST1H3D testis cells in seminiferous ducts High Supported NA +ENSG00000197409 HIST1H3D testis Leydig cells High Supported NA +ENSG00000197417 SHPK prostate glandular cells Medium Enhanced Q9UHJ6 +ENSG00000197417 SHPK seminal vesicle glandular cells Medium Enhanced Q9UHJ6 +ENSG00000197417 SHPK testis Leydig cells Medium Enhanced Q9UHJ6 +ENSG00000197444 OGDHL epididymis glandular cells Low Enhanced Q9ULD0 +ENSG00000197444 OGDHL seminal vesicle glandular cells Low Enhanced Q9ULD0 +ENSG00000197448 GSTK1 epididymis glandular cells High Enhanced Q9Y2Q3 +ENSG00000197448 GSTK1 prostate glandular cells Low Enhanced Q9Y2Q3 +ENSG00000197448 GSTK1 testis cells in seminiferous ducts Low Enhanced Q9Y2Q3 +ENSG00000197448 GSTK1 testis Leydig cells High Enhanced Q9Y2Q3 +ENSG00000197498 RPF2 epididymis glandular cells Medium Supported Q9H7B2 +ENSG00000197498 RPF2 seminal vesicle glandular cells Low Supported Q9H7B2 +ENSG00000197498 RPF2 testis cells in seminiferous ducts Low Supported Q9H7B2 +ENSG00000197498 RPF2 testis Leydig cells Medium Supported Q9H7B2 +ENSG00000197548 ATG7 epididymis glandular cells Medium Supported O95352 +ENSG00000197548 ATG7 prostate glandular cells Medium Supported O95352 +ENSG00000197548 ATG7 seminal vesicle glandular cells Low Supported O95352 +ENSG00000197548 ATG7 testis cells in seminiferous ducts Medium Supported O95352 +ENSG00000197548 ATG7 testis Leydig cells Medium Supported O95352 +ENSG00000197557 TTC30A epididymis glandular cells Medium Supported Q86WT1 +ENSG00000197557 TTC30A testis cells in seminiferous ducts High Supported Q86WT1 +ENSG00000197579 TOPORS epididymis glandular cells High Enhanced Q9NS56 +ENSG00000197579 TOPORS prostate glandular cells High Enhanced Q9NS56 +ENSG00000197579 TOPORS seminal vesicle glandular cells High Enhanced Q9NS56 +ENSG00000197579 TOPORS testis cells in seminiferous ducts High Enhanced Q9NS56 +ENSG00000197579 TOPORS testis Leydig cells High Enhanced Q9NS56 +ENSG00000197594 ENPP1 epididymis glandular cells Low Enhanced P22413 +ENSG00000197594 ENPP1 seminal vesicle glandular cells Low Enhanced P22413 +ENSG00000197594 ENPP1 testis Leydig cells Medium Enhanced P22413 +ENSG00000197635 DPP4 prostate glandular cells High Enhanced P27487 +ENSG00000197635 DPP4 seminal vesicle glandular cells High Enhanced P27487 +ENSG00000197653 DNAH10 testis cells in seminiferous ducts High Enhanced Q8IVF4 +ENSG00000197653 DNAH10 testis Leydig cells Medium Enhanced Q8IVF4 +ENSG00000197694 SPTAN1 epididymis glandular cells Medium Enhanced Q13813 +ENSG00000197694 SPTAN1 prostate glandular cells Medium Enhanced Q13813 +ENSG00000197694 SPTAN1 seminal vesicle glandular cells High Enhanced Q13813 +ENSG00000197694 SPTAN1 testis cells in seminiferous ducts Medium Enhanced Q13813 +ENSG00000197694 SPTAN1 testis Leydig cells Medium Enhanced Q13813 +ENSG00000197746 PSAP epididymis glandular cells High Enhanced P07602 +ENSG00000197746 PSAP prostate glandular cells High Enhanced P07602 +ENSG00000197746 PSAP seminal vesicle glandular cells High Enhanced P07602 +ENSG00000197746 PSAP testis cells in seminiferous ducts High Enhanced P07602 +ENSG00000197746 PSAP testis Leydig cells High Enhanced P07602 +ENSG00000197747 S100A10 epididymis glandular cells Medium Enhanced P60903 +ENSG00000197747 S100A10 prostate glandular cells High Enhanced P60903 +ENSG00000197747 S100A10 seminal vesicle glandular cells Medium Enhanced P60903 +ENSG00000197747 S100A10 testis cells in seminiferous ducts Low Enhanced P60903 +ENSG00000197747 S100A10 testis Leydig cells Medium Enhanced P60903 +ENSG00000197822 OCLN epididymis glandular cells Low Enhanced Q16625 +ENSG00000197822 OCLN prostate glandular cells Low Enhanced Q16625 +ENSG00000197822 OCLN seminal vesicle glandular cells Low Enhanced Q16625 +ENSG00000197822 OCLN testis Leydig cells Medium Enhanced Q16625 +ENSG00000197837 HIST4H4 epididymis glandular cells High Supported NA +ENSG00000197837 HIST4H4 prostate glandular cells High Supported NA +ENSG00000197837 HIST4H4 seminal vesicle glandular cells Medium Supported NA +ENSG00000197837 HIST4H4 testis cells in seminiferous ducts High Supported NA +ENSG00000197837 HIST4H4 testis Leydig cells Medium Supported NA +ENSG00000197857 ZNF44 epididymis glandular cells High Supported P15621 +ENSG00000197857 ZNF44 prostate glandular cells Medium Supported P15621 +ENSG00000197857 ZNF44 seminal vesicle glandular cells Medium Supported P15621 +ENSG00000197857 ZNF44 testis cells in seminiferous ducts High Supported P15621 +ENSG00000197857 ZNF44 testis Leydig cells Medium Supported P15621 +ENSG00000197860 SGTB prostate glandular cells Low Enhanced Q96EQ0 +ENSG00000197860 SGTB testis cells in seminiferous ducts Low Enhanced Q96EQ0 +ENSG00000197879 MYO1C epididymis glandular cells Medium Enhanced O00159 +ENSG00000197879 MYO1C prostate glandular cells Medium Enhanced O00159 +ENSG00000197879 MYO1C seminal vesicle glandular cells Medium Enhanced O00159 +ENSG00000197879 MYO1C testis cells in seminiferous ducts Medium Enhanced O00159 +ENSG00000197879 MYO1C testis Leydig cells High Enhanced O00159 +ENSG00000197892 KIF13B epididymis glandular cells Medium Enhanced Q9NQT8 +ENSG00000197892 KIF13B seminal vesicle glandular cells Medium Enhanced Q9NQT8 +ENSG00000197892 KIF13B testis cells in seminiferous ducts Low Enhanced Q9NQT8 +ENSG00000197903 HIST1H2BK epididymis glandular cells High Supported O60814 +ENSG00000197903 HIST1H2BK prostate glandular cells High Supported O60814 +ENSG00000197903 HIST1H2BK seminal vesicle glandular cells High Supported O60814 +ENSG00000197903 HIST1H2BK testis cells in seminiferous ducts High Supported O60814 +ENSG00000197903 HIST1H2BK testis Leydig cells High Supported O60814 +ENSG00000197921 HES5 testis cells in seminiferous ducts Medium Enhanced NA +ENSG00000197930 ERO1A prostate glandular cells Low Enhanced Q96HE7 +ENSG00000197930 ERO1A seminal vesicle glandular cells Low Enhanced Q96HE7 +ENSG00000197930 ERO1A testis cells in seminiferous ducts Low Enhanced Q96HE7 +ENSG00000197943 PLCG2 epididymis glandular cells Low Enhanced P16885 +ENSG00000197943 PLCG2 seminal vesicle glandular cells Low Enhanced P16885 +ENSG00000197943 PLCG2 testis cells in seminiferous ducts Low Enhanced P16885 +ENSG00000197943 PLCG2 testis Leydig cells Low Enhanced P16885 +ENSG00000197956 S100A6 epididymis glandular cells Medium Enhanced P06703 +ENSG00000197956 S100A6 prostate glandular cells Medium Enhanced P06703 +ENSG00000197956 S100A6 seminal vesicle glandular cells Medium Enhanced P06703 +ENSG00000197956 S100A6 testis Leydig cells High Enhanced P06703 +ENSG00000197969 VPS13A epididymis glandular cells Medium Enhanced Q96RL7 +ENSG00000197969 VPS13A prostate glandular cells Medium Enhanced Q96RL7 +ENSG00000197969 VPS13A seminal vesicle glandular cells Low Enhanced Q96RL7 +ENSG00000197969 VPS13A testis cells in seminiferous ducts High Enhanced Q96RL7 +ENSG00000197969 VPS13A testis Leydig cells High Enhanced Q96RL7 +ENSG00000197976 AKAP17A epididymis glandular cells Medium Enhanced Q02040 +ENSG00000197976 AKAP17A prostate glandular cells Medium Enhanced Q02040 +ENSG00000197976 AKAP17A seminal vesicle glandular cells Medium Enhanced Q02040 +ENSG00000197976 AKAP17A testis cells in seminiferous ducts High Enhanced Q02040 +ENSG00000197976 AKAP17A testis Leydig cells Low Enhanced Q02040 +ENSG00000198003 CCDC151 testis preleptotene spermatocytes Medium Enhanced A5D8V7 +ENSG00000198021 SPANXA1 testis cells in seminiferous ducts Medium Supported NA +ENSG00000198034 RPS4X epididymis glandular cells Medium Supported P62701 +ENSG00000198034 RPS4X prostate glandular cells Medium Supported P62701 +ENSG00000198034 RPS4X seminal vesicle glandular cells Medium Supported P62701 +ENSG00000198034 RPS4X testis cells in seminiferous ducts High Supported P62701 +ENSG00000198034 RPS4X testis Leydig cells High Supported P62701 +ENSG00000198053 SIRPA epididymis glandular cells Low Enhanced P78324 +ENSG00000198053 SIRPA prostate glandular cells Low Enhanced P78324 +ENSG00000198053 SIRPA testis Leydig cells Low Enhanced P78324 +ENSG00000198087 CD2AP epididymis glandular cells Low Enhanced Q9Y5K6 +ENSG00000198087 CD2AP prostate glandular cells Medium Enhanced Q9Y5K6 +ENSG00000198087 CD2AP seminal vesicle glandular cells Medium Enhanced Q9Y5K6 +ENSG00000198087 CD2AP testis cells in seminiferous ducts Medium Enhanced Q9Y5K6 +ENSG00000198087 CD2AP testis Leydig cells Medium Enhanced Q9Y5K6 +ENSG00000198113 TOR4A prostate glandular cells Low Enhanced Q9NXH8 +ENSG00000198113 TOR4A seminal vesicle glandular cells Low Enhanced Q9NXH8 +ENSG00000198113 TOR4A testis cells in seminiferous ducts Medium Enhanced Q9NXH8 +ENSG00000198113 TOR4A testis Leydig cells Medium Enhanced Q9NXH8 +ENSG00000198130 HIBCH epididymis glandular cells Medium Enhanced Q6NVY1 +ENSG00000198130 HIBCH prostate glandular cells High Enhanced Q6NVY1 +ENSG00000198130 HIBCH seminal vesicle glandular cells High Enhanced Q6NVY1 +ENSG00000198130 HIBCH testis cells in seminiferous ducts High Enhanced Q6NVY1 +ENSG00000198130 HIBCH testis Leydig cells High Enhanced Q6NVY1 +ENSG00000198142 SOWAHC epididymis glandular cells Low Enhanced Q53LP3 +ENSG00000198142 SOWAHC prostate glandular cells Medium Enhanced Q53LP3 +ENSG00000198142 SOWAHC seminal vesicle glandular cells Medium Enhanced Q53LP3 +ENSG00000198142 SOWAHC testis cells in seminiferous ducts Medium Enhanced Q53LP3 +ENSG00000198142 SOWAHC testis Leydig cells Low Enhanced Q53LP3 +ENSG00000198160 MIER1 epididymis glandular cells Low Enhanced Q8N108 +ENSG00000198160 MIER1 prostate glandular cells Medium Enhanced Q8N108 +ENSG00000198160 MIER1 seminal vesicle glandular cells Medium Enhanced Q8N108 +ENSG00000198160 MIER1 testis cells in seminiferous ducts High Enhanced Q8N108 +ENSG00000198160 MIER1 testis Leydig cells Medium Enhanced Q8N108 +ENSG00000198162 MAN1A2 epididymis glandular cells High Enhanced O60476 +ENSG00000198162 MAN1A2 prostate glandular cells Medium Enhanced O60476 +ENSG00000198162 MAN1A2 seminal vesicle glandular cells High Enhanced O60476 +ENSG00000198162 MAN1A2 testis Leydig cells Medium Enhanced O60476 +ENSG00000198176 TFDP1 epididymis glandular cells Medium Enhanced Q14186 +ENSG00000198176 TFDP1 prostate glandular cells Medium Enhanced Q14186 +ENSG00000198176 TFDP1 seminal vesicle glandular cells Medium Enhanced Q14186 +ENSG00000198176 TFDP1 testis cells in seminiferous ducts Medium Enhanced Q14186 +ENSG00000198176 TFDP1 testis Leydig cells Medium Enhanced Q14186 +ENSG00000198231 DDX42 epididymis glandular cells Medium Enhanced Q86XP3 +ENSG00000198231 DDX42 prostate glandular cells Medium Enhanced Q86XP3 +ENSG00000198231 DDX42 seminal vesicle glandular cells Medium Enhanced Q86XP3 +ENSG00000198231 DDX42 testis cells in seminiferous ducts High Enhanced Q86XP3 +ENSG00000198231 DDX42 testis Leydig cells High Enhanced Q86XP3 +ENSG00000198483 ANKRD35 epididymis glandular cells Low Enhanced Q8N283 +ENSG00000198483 ANKRD35 seminal vesicle glandular cells Low Enhanced Q8N283 +ENSG00000198483 ANKRD35 testis Leydig cells Low Enhanced Q8N283 +ENSG00000198513 ATL1 epididymis glandular cells Medium Enhanced Q8WXF7 +ENSG00000198513 ATL1 prostate glandular cells Medium Enhanced Q8WXF7 +ENSG00000198513 ATL1 seminal vesicle glandular cells Medium Enhanced Q8WXF7 +ENSG00000198513 ATL1 testis cells in seminiferous ducts Medium Enhanced Q8WXF7 +ENSG00000198513 ATL1 testis Leydig cells Medium Enhanced Q8WXF7 +ENSG00000198554 WDHD1 prostate glandular cells Low Enhanced O75717 +ENSG00000198554 WDHD1 testis cells in seminiferous ducts High Enhanced O75717 +ENSG00000198561 CTNND1 epididymis glandular cells Medium Enhanced O60716 +ENSG00000198561 CTNND1 prostate glandular cells Medium Enhanced O60716 +ENSG00000198561 CTNND1 seminal vesicle glandular cells Medium Enhanced O60716 +ENSG00000198561 CTNND1 testis cells in seminiferous ducts Medium Enhanced O60716 +ENSG00000198561 CTNND1 testis Leydig cells Low Enhanced O60716 +ENSG00000198563 DDX39B epididymis glandular cells Medium Enhanced NA +ENSG00000198563 DDX39B prostate glandular cells Medium Enhanced NA +ENSG00000198563 DDX39B seminal vesicle glandular cells Low Enhanced NA +ENSG00000198563 DDX39B testis cells in seminiferous ducts Medium Enhanced NA +ENSG00000198563 DDX39B testis Leydig cells Low Enhanced NA +ENSG00000198573 SPANXC testis cells in seminiferous ducts Medium Supported Q9NY87 +ENSG00000198604 BAZ1A epididymis glandular cells Medium Supported Q9NRL2 +ENSG00000198604 BAZ1A prostate glandular cells Low Supported Q9NRL2 +ENSG00000198604 BAZ1A seminal vesicle glandular cells Low Supported Q9NRL2 +ENSG00000198604 BAZ1A testis cells in seminiferous ducts High Supported Q9NRL2 +ENSG00000198604 BAZ1A testis Leydig cells Low Supported Q9NRL2 +ENSG00000198646 NCOA6 epididymis glandular cells High Supported Q14686 +ENSG00000198646 NCOA6 prostate glandular cells Medium Supported Q14686 +ENSG00000198646 NCOA6 seminal vesicle glandular cells Medium Supported Q14686 +ENSG00000198646 NCOA6 testis cells in seminiferous ducts Medium Supported Q14686 +ENSG00000198646 NCOA6 testis Leydig cells Medium Supported Q14686 +ENSG00000198648 STK39 epididymis glandular cells Medium Enhanced Q9UEW8 +ENSG00000198648 STK39 prostate glandular cells Medium Enhanced Q9UEW8 +ENSG00000198648 STK39 seminal vesicle glandular cells Medium Enhanced Q9UEW8 +ENSG00000198648 STK39 testis cells in seminiferous ducts Medium Enhanced Q9UEW8 +ENSG00000198648 STK39 testis Leydig cells Medium Enhanced Q9UEW8 +ENSG00000198668 CALM1 epididymis glandular cells Low Supported P0DP23 +ENSG00000198668 CALM1 prostate glandular cells Medium Supported P0DP23 +ENSG00000198668 CALM1 seminal vesicle glandular cells Low Supported P0DP23 +ENSG00000198668 CALM1 testis cells in seminiferous ducts Medium Supported P0DP23 +ENSG00000198668 CALM1 testis Leydig cells Low Supported P0DP23 +ENSG00000198681 MAGEA1 testis cells in seminiferous ducts High Enhanced P43355 +ENSG00000198689 SLC9A6 epididymis glandular cells Medium Enhanced Q92581 +ENSG00000198689 SLC9A6 prostate glandular cells Low Enhanced Q92581 +ENSG00000198689 SLC9A6 testis cells in seminiferous ducts High Enhanced Q92581 +ENSG00000198689 SLC9A6 testis Leydig cells Low Enhanced Q92581 +ENSG00000198712 MT-CO2 epididymis glandular cells High Enhanced P00403 +ENSG00000198712 MT-CO2 prostate glandular cells High Enhanced P00403 +ENSG00000198712 MT-CO2 seminal vesicle glandular cells High Enhanced P00403 +ENSG00000198712 MT-CO2 testis cells in seminiferous ducts High Enhanced P00403 +ENSG00000198712 MT-CO2 testis Leydig cells High Enhanced P00403 +ENSG00000198721 ECI2 epididymis glandular cells High Enhanced O75521 +ENSG00000198721 ECI2 prostate glandular cells Medium Enhanced O75521 +ENSG00000198721 ECI2 seminal vesicle glandular cells Medium Enhanced O75521 +ENSG00000198721 ECI2 testis cells in seminiferous ducts Medium Enhanced O75521 +ENSG00000198721 ECI2 testis Leydig cells Medium Enhanced O75521 +ENSG00000198727 MT-CYB prostate glandular cells Medium Enhanced P00156 +ENSG00000198727 MT-CYB seminal vesicle glandular cells Medium Enhanced P00156 +ENSG00000198727 MT-CYB testis cells in seminiferous ducts Low Enhanced P00156 +ENSG00000198727 MT-CYB testis Leydig cells Medium Enhanced P00156 +ENSG00000198730 CTR9 epididymis glandular cells Medium Enhanced Q6PD62 +ENSG00000198730 CTR9 testis cells in seminiferous ducts Medium Enhanced Q6PD62 +ENSG00000198730 CTR9 testis Leydig cells Low Enhanced Q6PD62 +ENSG00000198754 OXCT2 testis cells in seminiferous ducts Medium Enhanced Q9BYC2 +ENSG00000198765 SYCP1 testis preleptotene spermatocytes Low Enhanced Q15431 +ENSG00000198765 SYCP1 testis spermatogonia Medium Enhanced Q15431 +ENSG00000198780 FAM169A epididymis glandular cells High Enhanced Q9Y6X4 +ENSG00000198780 FAM169A prostate glandular cells Low Enhanced Q9Y6X4 +ENSG00000198780 FAM169A seminal vesicle glandular cells Medium Enhanced Q9Y6X4 +ENSG00000198780 FAM169A testis elongated or late spermatids Low Enhanced Q9Y6X4 +ENSG00000198780 FAM169A testis sertoli cells High Enhanced Q9Y6X4 +ENSG00000198780 FAM169A testis spermatogonia Low Enhanced Q9Y6X4 +ENSG00000198783 ZNF830 epididymis glandular cells Medium Enhanced Q96NB3 +ENSG00000198783 ZNF830 prostate glandular cells High Enhanced Q96NB3 +ENSG00000198783 ZNF830 seminal vesicle glandular cells High Enhanced Q96NB3 +ENSG00000198783 ZNF830 testis cells in seminiferous ducts High Enhanced Q96NB3 +ENSG00000198783 ZNF830 testis Leydig cells High Enhanced Q96NB3 +ENSG00000198794 SCAMP5 epididymis glandular cells Medium Enhanced Q8TAC9 +ENSG00000198794 SCAMP5 prostate glandular cells Medium Enhanced Q8TAC9 +ENSG00000198794 SCAMP5 testis cells in seminiferous ducts Low Enhanced Q8TAC9 +ENSG00000198795 ZNF521 epididymis glandular cells Medium Enhanced Q96K83 +ENSG00000198795 ZNF521 prostate glandular cells Medium Enhanced Q96K83 +ENSG00000198795 ZNF521 seminal vesicle glandular cells Low Enhanced Q96K83 +ENSG00000198795 ZNF521 testis cells in seminiferous ducts Medium Enhanced Q96K83 +ENSG00000198795 ZNF521 testis Leydig cells Medium Enhanced Q96K83 +ENSG00000198804 MT-CO1 epididymis glandular cells Medium Enhanced P00395 +ENSG00000198804 MT-CO1 prostate glandular cells Medium Enhanced P00395 +ENSG00000198804 MT-CO1 seminal vesicle glandular cells High Enhanced P00395 +ENSG00000198804 MT-CO1 testis cells in seminiferous ducts Medium Enhanced P00395 +ENSG00000198804 MT-CO1 testis Leydig cells High Enhanced P00395 +ENSG00000198805 PNP epididymis glandular cells High Enhanced P00491 +ENSG00000198805 PNP seminal vesicle glandular cells Low Enhanced P00491 +ENSG00000198805 PNP testis cells in seminiferous ducts Low Enhanced P00491 +ENSG00000198824 CHAMP1 epididymis glandular cells High Enhanced Q96JM3 +ENSG00000198824 CHAMP1 prostate glandular cells High Enhanced Q96JM3 +ENSG00000198824 CHAMP1 seminal vesicle glandular cells High Enhanced Q96JM3 +ENSG00000198824 CHAMP1 testis cells in seminiferous ducts High Enhanced Q96JM3 +ENSG00000198824 CHAMP1 testis Leydig cells Medium Enhanced Q96JM3 +ENSG00000198826 ARHGAP11A seminal vesicle glandular cells Low Enhanced H3BR51 +ENSG00000198826 ARHGAP11A testis cells in seminiferous ducts Low Enhanced H3BR51 +ENSG00000198826 ARHGAP11A testis Leydig cells Medium Enhanced H3BR51 +ENSG00000198830 HMGN2 epididymis glandular cells High Supported P05204 +ENSG00000198830 HMGN2 prostate glandular cells Medium Supported P05204 +ENSG00000198830 HMGN2 seminal vesicle glandular cells Medium Supported P05204 +ENSG00000198830 HMGN2 testis cells in seminiferous ducts Low Supported P05204 +ENSG00000198830 HMGN2 testis Leydig cells Low Supported P05204 +ENSG00000198833 UBE2J1 epididymis glandular cells Medium Enhanced Q9Y385 +ENSG00000198833 UBE2J1 prostate glandular cells Low Enhanced Q9Y385 +ENSG00000198833 UBE2J1 seminal vesicle glandular cells Low Enhanced Q9Y385 +ENSG00000198833 UBE2J1 testis cells in seminiferous ducts Medium Enhanced Q9Y385 +ENSG00000198833 UBE2J1 testis Leydig cells Low Enhanced Q9Y385 +ENSG00000198836 OPA1 epididymis glandular cells Medium Enhanced O60313 +ENSG00000198836 OPA1 prostate glandular cells Low Enhanced O60313 +ENSG00000198836 OPA1 seminal vesicle glandular cells Medium Enhanced O60313 +ENSG00000198836 OPA1 testis cells in seminiferous ducts Medium Enhanced O60313 +ENSG00000198836 OPA1 testis Leydig cells Medium Enhanced O60313 +ENSG00000198840 MT-ND3 epididymis glandular cells Low Enhanced P03897 +ENSG00000198840 MT-ND3 prostate glandular cells Medium Enhanced P03897 +ENSG00000198840 MT-ND3 seminal vesicle glandular cells Medium Enhanced P03897 +ENSG00000198840 MT-ND3 testis cells in seminiferous ducts Medium Enhanced P03897 +ENSG00000198840 MT-ND3 testis Leydig cells Medium Enhanced P03897 +ENSG00000198846 TOX prostate glandular cells Low Enhanced O94900 +ENSG00000198846 TOX testis cells in seminiferous ducts Low Enhanced O94900 +ENSG00000198846 TOX testis Leydig cells Low Enhanced O94900 +ENSG00000198848 CES1 testis cells in seminiferous ducts Low Enhanced H3BQV8 +ENSG00000198883 PNMA5 testis pachytene spermatocytes High Enhanced Q96PV4 +ENSG00000198883 PNMA5 testis preleptotene spermatocytes High Enhanced Q96PV4 +ENSG00000198883 PNMA5 testis spermatogonia Medium Enhanced Q96PV4 +ENSG00000198887 SMC5 epididymis glandular cells Medium Enhanced Q8IY18 +ENSG00000198887 SMC5 prostate glandular cells High Enhanced Q8IY18 +ENSG00000198887 SMC5 seminal vesicle glandular cells Medium Enhanced Q8IY18 +ENSG00000198887 SMC5 testis cells in seminiferous ducts High Enhanced Q8IY18 +ENSG00000198887 SMC5 testis Leydig cells Medium Enhanced Q8IY18 +ENSG00000198900 TOP1 epididymis glandular cells High Enhanced P11387 +ENSG00000198900 TOP1 prostate glandular cells Medium Enhanced P11387 +ENSG00000198900 TOP1 seminal vesicle glandular cells Medium Enhanced P11387 +ENSG00000198900 TOP1 testis cells in seminiferous ducts Medium Enhanced P11387 +ENSG00000198900 TOP1 testis Leydig cells Medium Enhanced P11387 +ENSG00000198901 PRC1 epididymis glandular cells Medium Enhanced O43663 +ENSG00000198901 PRC1 prostate glandular cells Medium Enhanced O43663 +ENSG00000198901 PRC1 seminal vesicle glandular cells Medium Enhanced O43663 +ENSG00000198901 PRC1 testis cells in seminiferous ducts High Enhanced O43663 +ENSG00000198901 PRC1 testis Leydig cells Medium Enhanced O43663 +ENSG00000198910 L1CAM epididymis glandular cells Low Enhanced P32004 +ENSG00000198910 L1CAM prostate glandular cells Low Enhanced P32004 +ENSG00000198910 L1CAM seminal vesicle glandular cells Medium Enhanced P32004 +ENSG00000198915 RASGEF1A prostate glandular cells Low Enhanced Q8N9B8 +ENSG00000198915 RASGEF1A seminal vesicle glandular cells Low Enhanced Q8N9B8 +ENSG00000198915 RASGEF1A testis Leydig cells Low Enhanced Q8N9B8 +ENSG00000198920 KIAA0753 epididymis glandular cells High Enhanced Q2KHM9 +ENSG00000198920 KIAA0753 prostate glandular cells Low Enhanced Q2KHM9 +ENSG00000198920 KIAA0753 seminal vesicle glandular cells High Enhanced Q2KHM9 +ENSG00000198920 KIAA0753 testis cells in seminiferous ducts Medium Enhanced Q2KHM9 +ENSG00000198920 KIAA0753 testis Leydig cells Medium Enhanced Q2KHM9 +ENSG00000198951 NAGA epididymis glandular cells High Enhanced P17050 +ENSG00000198951 NAGA prostate glandular cells Medium Enhanced P17050 +ENSG00000198951 NAGA seminal vesicle glandular cells High Enhanced P17050 +ENSG00000198951 NAGA testis cells in seminiferous ducts Medium Enhanced P17050 +ENSG00000198951 NAGA testis Leydig cells Medium Enhanced P17050 +ENSG00000198959 TGM2 testis Leydig cells Low Enhanced P21980 +ENSG00000198961 PJA2 epididymis glandular cells Low Enhanced O43164 +ENSG00000198961 PJA2 prostate glandular cells Medium Enhanced O43164 +ENSG00000198961 PJA2 seminal vesicle glandular cells Medium Enhanced O43164 +ENSG00000198961 PJA2 testis cells in seminiferous ducts Medium Enhanced O43164 +ENSG00000198961 PJA2 testis Leydig cells Medium Enhanced O43164 +ENSG00000203668 CHML epididymis glandular cells Low Supported P26374 +ENSG00000203668 CHML prostate glandular cells Low Supported P26374 +ENSG00000203668 CHML seminal vesicle glandular cells Medium Supported P26374 +ENSG00000203668 CHML testis cells in seminiferous ducts Medium Supported P26374 +ENSG00000203668 CHML testis Leydig cells Medium Supported P26374 +ENSG00000203784 LELP1 testis elongated or late spermatids High Enhanced Q5T871 +ENSG00000203795 FAM24A testis cells in seminiferous ducts High Supported A6NFZ4 +ENSG00000203795 FAM24A testis Leydig cells High Supported A6NFZ4 +ENSG00000203797 DDO epididymis glandular cells High Enhanced Q99489 +ENSG00000203797 DDO prostate glandular cells High Enhanced Q99489 +ENSG00000203797 DDO seminal vesicle glandular cells High Enhanced Q99489 +ENSG00000203797 DDO testis cells in seminiferous ducts High Enhanced Q99489 +ENSG00000203797 DDO testis Leydig cells Medium Enhanced Q99489 +ENSG00000203811 HIST2H3C epididymis glandular cells High Supported NA +ENSG00000203811 HIST2H3C prostate glandular cells High Supported NA +ENSG00000203811 HIST2H3C seminal vesicle glandular cells High Supported NA +ENSG00000203811 HIST2H3C testis cells in seminiferous ducts High Supported NA +ENSG00000203811 HIST2H3C testis Leydig cells High Supported NA +ENSG00000203812 HIST2H2AA3 epididymis glandular cells Medium Supported NA +ENSG00000203812 HIST2H2AA3 prostate glandular cells Low Supported NA +ENSG00000203812 HIST2H2AA3 seminal vesicle glandular cells Medium Supported NA +ENSG00000203812 HIST2H2AA3 testis cells in seminiferous ducts High Supported NA +ENSG00000203812 HIST2H2AA3 testis Leydig cells Low Supported NA +ENSG00000203814 HIST2H2BF epididymis glandular cells High Supported Q5QNW6 +ENSG00000203814 HIST2H2BF prostate glandular cells High Supported Q5QNW6 +ENSG00000203814 HIST2H2BF seminal vesicle glandular cells High Supported Q5QNW6 +ENSG00000203814 HIST2H2BF testis cells in seminiferous ducts High Supported Q5QNW6 +ENSG00000203814 HIST2H2BF testis Leydig cells High Supported Q5QNW6 +ENSG00000203818 HIST2H3PS2 epididymis glandular cells High Supported Q5TEC6 +ENSG00000203818 HIST2H3PS2 prostate glandular cells High Supported Q5TEC6 +ENSG00000203818 HIST2H3PS2 seminal vesicle glandular cells High Supported Q5TEC6 +ENSG00000203818 HIST2H3PS2 testis cells in seminiferous ducts High Supported Q5TEC6 +ENSG00000203818 HIST2H3PS2 testis Leydig cells High Supported Q5TEC6 +ENSG00000203852 HIST2H3A epididymis glandular cells High Supported NA +ENSG00000203852 HIST2H3A prostate glandular cells High Supported NA +ENSG00000203852 HIST2H3A seminal vesicle glandular cells High Supported NA +ENSG00000203852 HIST2H3A testis cells in seminiferous ducts High Supported NA +ENSG00000203852 HIST2H3A testis Leydig cells High Supported NA +ENSG00000203859 HSD3B2 testis cells in seminiferous ducts Low Supported P26439 +ENSG00000203879 GDI1 epididymis glandular cells High Enhanced P31150 +ENSG00000203879 GDI1 prostate glandular cells Medium Enhanced P31150 +ENSG00000203879 GDI1 seminal vesicle glandular cells High Enhanced P31150 +ENSG00000203879 GDI1 testis cells in seminiferous ducts High Enhanced P31150 +ENSG00000203879 GDI1 testis Leydig cells High Enhanced P31150 +ENSG00000203926 SPANXA2 testis cells in seminiferous ducts Medium Supported NA +ENSG00000203942 C10orf62 testis cells in seminiferous ducts Medium Enhanced Q5T681 +ENSG00000203943 SAMD13 seminal vesicle glandular cells Low Enhanced Q5VXD3 +ENSG00000203943 SAMD13 testis elongated or late spermatids Medium Enhanced Q5VXD3 +ENSG00000203943 SAMD13 testis Leydig cells Medium Enhanced Q5VXD3 +ENSG00000203943 SAMD13 testis pachytene spermatocytes Medium Enhanced Q5VXD3 +ENSG00000203943 SAMD13 testis preleptotene spermatocytes Medium Enhanced Q5VXD3 +ENSG00000203943 SAMD13 testis spermatogonia Medium Enhanced Q5VXD3 +ENSG00000203965 EFCAB7 testis cells in seminiferous ducts High Enhanced A8K855 +ENSG00000203989 RHOXF2B testis pachytene spermatocytes Medium Supported P0C7M4 +ENSG00000203989 RHOXF2B testis preleptotene spermatocytes Medium Supported P0C7M4 +ENSG00000203989 RHOXF2B testis spermatogonia High Supported P0C7M4 +ENSG00000204052 LRRC73 testis elongated or late spermatids Low Enhanced Q5JTD7 +ENSG00000204052 LRRC73 testis round or early spermatids Medium Enhanced Q5JTD7 +ENSG00000204065 TCEAL5 testis elongated or late spermatids High Supported Q5H9L2 +ENSG00000204065 TCEAL5 testis round or early spermatids High Supported Q5H9L2 +ENSG00000204071 TCEAL6 testis elongated or late spermatids High Supported Q6IPX3 +ENSG00000204071 TCEAL6 testis round or early spermatids High Supported Q6IPX3 +ENSG00000204140 CLPSL1 epididymis glandular cells Medium Enhanced A2RUU4 +ENSG00000204209 DAXX epididymis glandular cells Medium Enhanced NA +ENSG00000204209 DAXX prostate glandular cells Low Enhanced NA +ENSG00000204209 DAXX seminal vesicle glandular cells Medium Enhanced NA +ENSG00000204209 DAXX testis cells in seminiferous ducts High Enhanced NA +ENSG00000204209 DAXX testis Leydig cells Medium Enhanced NA +ENSG00000204220 PFDN6 epididymis glandular cells Medium Enhanced NA +ENSG00000204220 PFDN6 prostate glandular cells Medium Enhanced NA +ENSG00000204220 PFDN6 seminal vesicle glandular cells Medium Enhanced NA +ENSG00000204220 PFDN6 testis cells in seminiferous ducts Medium Enhanced NA +ENSG00000204220 PFDN6 testis Leydig cells Low Enhanced NA +ENSG00000204227 RING1 epididymis glandular cells Medium Supported NA +ENSG00000204227 RING1 prostate glandular cells Medium Supported NA +ENSG00000204227 RING1 seminal vesicle glandular cells Medium Supported NA +ENSG00000204227 RING1 testis cells in seminiferous ducts Medium Supported NA +ENSG00000204227 RING1 testis Leydig cells Low Supported NA +ENSG00000204228 HSD17B8 epididymis glandular cells Medium Enhanced NA +ENSG00000204228 HSD17B8 prostate glandular cells Medium Enhanced NA +ENSG00000204228 HSD17B8 seminal vesicle glandular cells High Enhanced NA +ENSG00000204228 HSD17B8 testis cells in seminiferous ducts Low Enhanced NA +ENSG00000204228 HSD17B8 testis Leydig cells High Enhanced NA +ENSG00000204231 RXRB epididymis glandular cells High Supported NA +ENSG00000204231 RXRB prostate glandular cells Medium Supported NA +ENSG00000204231 RXRB seminal vesicle glandular cells High Supported NA +ENSG00000204231 RXRB testis cells in seminiferous ducts Low Supported NA +ENSG00000204231 RXRB testis Leydig cells High Supported NA +ENSG00000204252 HLA-DOA epididymis glandular cells Low Enhanced F6WU08 +ENSG00000204252 HLA-DOA prostate glandular cells Low Enhanced F6WU08 +ENSG00000204252 HLA-DOA seminal vesicle glandular cells Low Enhanced F6WU08 +ENSG00000204257 HLA-DMA epididymis glandular cells Medium Enhanced F6S093 +ENSG00000204257 HLA-DMA prostate glandular cells Low Enhanced F6S093 +ENSG00000204257 HLA-DMA testis Leydig cells Low Enhanced F6S093 +ENSG00000204264 PSMB8 epididymis glandular cells Medium Enhanced NA +ENSG00000204264 PSMB8 prostate glandular cells Medium Enhanced NA +ENSG00000204264 PSMB8 seminal vesicle glandular cells Medium Enhanced NA +ENSG00000204264 PSMB8 testis cells in seminiferous ducts Medium Enhanced NA +ENSG00000204264 PSMB8 testis Leydig cells Medium Enhanced NA +ENSG00000204287 HLA-DRA epididymis glandular cells Low Enhanced NA +ENSG00000204287 HLA-DRA seminal vesicle glandular cells Medium Enhanced NA +ENSG00000204304 PBX2 epididymis glandular cells Medium Enhanced NA +ENSG00000204304 PBX2 prostate glandular cells Medium Enhanced NA +ENSG00000204304 PBX2 seminal vesicle glandular cells Medium Enhanced NA +ENSG00000204304 PBX2 testis cells in seminiferous ducts Medium Enhanced NA +ENSG00000204304 PBX2 testis Leydig cells Medium Enhanced NA +ENSG00000204315 FKBPL epididymis glandular cells Medium Enhanced NA +ENSG00000204315 FKBPL prostate glandular cells Low Enhanced NA +ENSG00000204315 FKBPL seminal vesicle glandular cells Low Enhanced NA +ENSG00000204315 FKBPL testis cells in seminiferous ducts Medium Enhanced NA +ENSG00000204315 FKBPL testis Leydig cells Low Enhanced NA +ENSG00000204356 NELFE epididymis glandular cells High Enhanced E9PD43 +ENSG00000204356 NELFE prostate glandular cells Low Enhanced E9PD43 +ENSG00000204356 NELFE seminal vesicle glandular cells High Enhanced E9PD43 +ENSG00000204356 NELFE testis cells in seminiferous ducts High Enhanced E9PD43 +ENSG00000204356 NELFE testis Leydig cells Low Enhanced E9PD43 +ENSG00000204361 NXPE2 epididymis glandular cells Medium Enhanced Q96DL1 +ENSG00000204361 NXPE2 testis Leydig cells Low Enhanced Q96DL1 +ENSG00000204371 EHMT2 epididymis glandular cells Medium Supported NA +ENSG00000204371 EHMT2 prostate glandular cells Medium Supported NA +ENSG00000204371 EHMT2 seminal vesicle glandular cells Low Supported NA +ENSG00000204371 EHMT2 testis cells in seminiferous ducts High Supported NA +ENSG00000204371 EHMT2 testis Leydig cells Low Supported NA +ENSG00000204385 SLC44A4 epididymis glandular cells Low Enhanced NA +ENSG00000204385 SLC44A4 prostate glandular cells Medium Enhanced NA +ENSG00000204385 SLC44A4 testis Leydig cells Low Enhanced NA +ENSG00000204389 HSPA1A epididymis glandular cells High Supported NA +ENSG00000204389 HSPA1A prostate glandular cells High Supported NA +ENSG00000204389 HSPA1A seminal vesicle glandular cells High Supported NA +ENSG00000204389 HSPA1A testis cells in seminiferous ducts Medium Supported NA +ENSG00000204389 HSPA1A testis Leydig cells Medium Supported NA +ENSG00000204390 HSPA1L testis elongated or late spermatids High Enhanced NA +ENSG00000204390 HSPA1L testis pachytene spermatocytes Medium Enhanced NA +ENSG00000204390 HSPA1L testis preleptotene spermatocytes Low Enhanced NA +ENSG00000204390 HSPA1L testis round or early spermatids Medium Enhanced NA +ENSG00000204390 HSPA1L testis spermatogonia Low Enhanced NA +ENSG00000204392 LSM2 epididymis glandular cells High Supported NA +ENSG00000204392 LSM2 prostate glandular cells High Supported NA +ENSG00000204392 LSM2 seminal vesicle glandular cells High Supported NA +ENSG00000204392 LSM2 testis cells in seminiferous ducts High Supported NA +ENSG00000204392 LSM2 testis Leydig cells High Supported NA +ENSG00000204463 BAG6 epididymis glandular cells Medium Enhanced NA +ENSG00000204463 BAG6 prostate glandular cells Medium Enhanced NA +ENSG00000204463 BAG6 seminal vesicle glandular cells Low Enhanced NA +ENSG00000204463 BAG6 testis cells in seminiferous ducts High Enhanced NA +ENSG00000204463 BAG6 testis Leydig cells Medium Enhanced NA +ENSG00000204560 DHX16 epididymis glandular cells High Enhanced NA +ENSG00000204560 DHX16 prostate glandular cells High Enhanced NA +ENSG00000204560 DHX16 seminal vesicle glandular cells High Enhanced NA +ENSG00000204560 DHX16 testis cells in seminiferous ducts High Enhanced NA +ENSG00000204560 DHX16 testis Leydig cells High Enhanced NA +ENSG00000204568 MRPS18B epididymis glandular cells High Supported NA +ENSG00000204568 MRPS18B prostate glandular cells High Supported NA +ENSG00000204568 MRPS18B seminal vesicle glandular cells High Supported NA +ENSG00000204568 MRPS18B testis cells in seminiferous ducts High Supported NA +ENSG00000204568 MRPS18B testis Leydig cells High Supported NA +ENSG00000204569 PPP1R10 epididymis glandular cells High Enhanced NA +ENSG00000204569 PPP1R10 prostate glandular cells Low Enhanced NA +ENSG00000204569 PPP1R10 seminal vesicle glandular cells Medium Enhanced NA +ENSG00000204569 PPP1R10 testis cells in seminiferous ducts Medium Enhanced NA +ENSG00000204569 PPP1R10 testis Leydig cells High Enhanced NA +ENSG00000204592 HLA-E epididymis glandular cells Medium Enhanced NA +ENSG00000204592 HLA-E prostate glandular cells Low Enhanced NA +ENSG00000204592 HLA-E seminal vesicle glandular cells Low Enhanced NA +ENSG00000204592 HLA-E testis Leydig cells Low Enhanced NA +ENSG00000204815 TTC25 testis elongated or late spermatids Medium Enhanced Q96NG3 +ENSG00000204815 TTC25 testis round or early spermatids Medium Enhanced Q96NG3 +ENSG00000204842 ATXN2 epididymis glandular cells Low Enhanced Q99700 +ENSG00000204842 ATXN2 prostate glandular cells Low Enhanced Q99700 +ENSG00000204842 ATXN2 seminal vesicle glandular cells Medium Enhanced Q99700 +ENSG00000204842 ATXN2 testis cells in seminiferous ducts Low Enhanced Q99700 +ENSG00000204842 ATXN2 testis Leydig cells Medium Enhanced Q99700 +ENSG00000204851 PNMAL2 epididymis glandular cells Low Enhanced Q9ULN7 +ENSG00000204851 PNMAL2 prostate glandular cells Low Enhanced Q9ULN7 +ENSG00000204851 PNMAL2 testis cells in seminiferous ducts Low Enhanced Q9ULN7 +ENSG00000204856 FAM216A testis elongated or late spermatids High Enhanced Q8WUB2 +ENSG00000204856 FAM216A testis round or early spermatids High Enhanced Q8WUB2 +ENSG00000204856 FAM216A testis sertoli cells High Enhanced Q8WUB2 +ENSG00000204977 TRIM13 prostate glandular cells Low Enhanced O60858 +ENSG00000204977 TRIM13 seminal vesicle glandular cells Low Enhanced O60858 +ENSG00000204977 TRIM13 testis cells in seminiferous ducts Medium Enhanced O60858 +ENSG00000205084 TMEM231 epididymis glandular cells Low Enhanced Q9H6L2 +ENSG00000205084 TMEM231 testis Leydig cells Low Enhanced Q9H6L2 +ENSG00000205085 FAM71F2 epididymis glandular cells Medium Enhanced Q6NXP2 +ENSG00000205085 FAM71F2 testis Leydig cells High Enhanced Q6NXP2 +ENSG00000205085 FAM71F2 testis sertoli cells High Enhanced Q6NXP2 +ENSG00000205090 TMEM240 epididymis glandular cells Low Supported Q5SV17 +ENSG00000205108 FAM205A testis cells in seminiferous ducts High Enhanced Q6ZU69 +ENSG00000205189 ZBTB10 epididymis glandular cells High Enhanced Q96DT7 +ENSG00000205189 ZBTB10 prostate glandular cells High Enhanced Q96DT7 +ENSG00000205189 ZBTB10 seminal vesicle glandular cells Medium Enhanced Q96DT7 +ENSG00000205189 ZBTB10 testis cells in seminiferous ducts High Enhanced Q96DT7 +ENSG00000205189 ZBTB10 testis Leydig cells High Enhanced Q96DT7 +ENSG00000205220 PSMB10 epididymis glandular cells Low Enhanced P40306 +ENSG00000205220 PSMB10 prostate glandular cells Medium Enhanced P40306 +ENSG00000205220 PSMB10 seminal vesicle glandular cells Low Enhanced P40306 +ENSG00000205301 MGAT4D testis Leydig cells High Enhanced A6NG13 +ENSG00000205323 SARNP epididymis glandular cells High Supported P82979 +ENSG00000205323 SARNP prostate glandular cells High Supported P82979 +ENSG00000205323 SARNP seminal vesicle glandular cells High Supported P82979 +ENSG00000205323 SARNP testis cells in seminiferous ducts High Supported P82979 +ENSG00000205323 SARNP testis Leydig cells Medium Supported P82979 +ENSG00000205359 SLCO6A1 testis elongated or late spermatids Medium Enhanced Q86UG4 +ENSG00000205359 SLCO6A1 testis Leydig cells Low Enhanced Q86UG4 +ENSG00000205359 SLCO6A1 testis round or early spermatids High Enhanced Q86UG4 +ENSG00000205359 SLCO6A1 testis sertoli cells High Enhanced Q86UG4 +ENSG00000205571 SMN2 epididymis glandular cells Medium Supported A0A1W2PRV5 +ENSG00000205571 SMN2 prostate glandular cells Medium Supported A0A1W2PRV5 +ENSG00000205571 SMN2 seminal vesicle glandular cells Low Supported A0A1W2PRV5 +ENSG00000205571 SMN2 testis cells in seminiferous ducts High Supported A0A1W2PRV5 +ENSG00000205571 SMN2 testis Leydig cells Medium Supported A0A1W2PRV5 +ENSG00000205581 HMGN1 epididymis glandular cells High Supported P05114 +ENSG00000205581 HMGN1 prostate glandular cells High Supported P05114 +ENSG00000205581 HMGN1 seminal vesicle glandular cells High Supported P05114 +ENSG00000205581 HMGN1 testis cells in seminiferous ducts High Supported P05114 +ENSG00000205581 HMGN1 testis Leydig cells High Supported P05114 +ENSG00000205609 EIF3CL epididymis glandular cells High Supported B5ME19 +ENSG00000205609 EIF3CL prostate glandular cells Medium Supported B5ME19 +ENSG00000205609 EIF3CL seminal vesicle glandular cells Medium Supported B5ME19 +ENSG00000205609 EIF3CL testis cells in seminiferous ducts Medium Supported B5ME19 +ENSG00000205609 EIF3CL testis Leydig cells High Supported B5ME19 +ENSG00000205642 VCX3B testis elongated or late spermatids Medium Supported Q9H321 +ENSG00000205642 VCX3B testis pachytene spermatocytes High Supported Q9H321 +ENSG00000205642 VCX3B testis preleptotene spermatocytes High Supported Q9H321 +ENSG00000205642 VCX3B testis round or early spermatids High Supported Q9H321 +ENSG00000205642 VCX3B testis spermatogonia High Supported Q9H321 +ENSG00000205683 DPF3 testis cells in seminiferous ducts High Enhanced Q92784 +ENSG00000205777 GAGE1 testis cells in seminiferous ducts High Supported Q13065 +ENSG00000205777 GAGE1 testis pachytene spermatocytes Low Supported Q13065 +ENSG00000205777 GAGE1 testis preleptotene spermatocytes High Supported Q13065 +ENSG00000205777 GAGE1 testis spermatogonia High Supported Q13065 +ENSG00000205838 TTC23L epididymis glandular cells Low Enhanced Q6PF05 +ENSG00000205838 TTC23L testis elongated or late spermatids Low Enhanced Q6PF05 +ENSG00000205838 TTC23L testis Leydig cells Low Enhanced Q6PF05 +ENSG00000205838 TTC23L testis pachytene spermatocytes High Enhanced Q6PF05 +ENSG00000205838 TTC23L testis preleptotene spermatocytes Low Enhanced Q6PF05 +ENSG00000205838 TTC23L testis round or early spermatids Medium Enhanced Q6PF05 +ENSG00000205838 TTC23L testis spermatogonia Low Enhanced Q6PF05 +ENSG00000205856 C22orf42 testis Leydig cells High Enhanced Q6IC83 +ENSG00000205856 C22orf42 testis preleptotene spermatocytes Low Enhanced Q6IC83 +ENSG00000205856 C22orf42 testis spermatogonia Medium Enhanced Q6IC83 +ENSG00000205884 DEFB136 epididymis glandular cells High Enhanced Q30KP8 +ENSG00000205929 C21orf62 epididymis glandular cells Medium Enhanced NA +ENSG00000205929 C21orf62 seminal vesicle glandular cells Medium Enhanced NA +ENSG00000206026 SMIM21 testis Leydig cells High Enhanced Q3B7S5 +ENSG00000206075 SERPINB5 epididymis glandular cells Low Enhanced P36952 +ENSG00000206075 SERPINB5 prostate glandular cells Low Enhanced P36952 +ENSG00000206075 SERPINB5 seminal vesicle glandular cells Low Enhanced P36952 +ENSG00000206075 SERPINB5 testis cells in seminiferous ducts Low Enhanced P36952 +ENSG00000206075 SERPINB5 testis Leydig cells Low Enhanced P36952 +ENSG00000212122 TSSK1B testis elongated or late spermatids High Enhanced Q9BXA7 +ENSG00000212122 TSSK1B testis round or early spermatids Low Enhanced Q9BXA7 +ENSG00000212123 PRR22 testis round or early spermatids High Enhanced Q8IZ63 +ENSG00000212719 C17orf51 epididymis glandular cells Medium Enhanced A8MQB3 +ENSG00000212719 C17orf51 prostate glandular cells Medium Enhanced A8MQB3 +ENSG00000212719 C17orf51 seminal vesicle glandular cells High Enhanced A8MQB3 +ENSG00000212719 C17orf51 testis cells in seminiferous ducts High Enhanced A8MQB3 +ENSG00000212719 C17orf51 testis Leydig cells Medium Enhanced A8MQB3 +ENSG00000213024 NUP62 epididymis glandular cells Low Enhanced P37198 +ENSG00000213024 NUP62 prostate glandular cells Low Enhanced P37198 +ENSG00000213024 NUP62 seminal vesicle glandular cells Low Enhanced P37198 +ENSG00000213024 NUP62 testis cells in seminiferous ducts Medium Enhanced P37198 +ENSG00000213024 NUP62 testis Leydig cells Medium Enhanced P37198 +ENSG00000213079 SCAF8 epididymis glandular cells High Enhanced Q9UPN6 +ENSG00000213079 SCAF8 prostate glandular cells High Enhanced Q9UPN6 +ENSG00000213079 SCAF8 seminal vesicle glandular cells High Enhanced Q9UPN6 +ENSG00000213079 SCAF8 testis cells in seminiferous ducts High Enhanced Q9UPN6 +ENSG00000213079 SCAF8 testis Leydig cells High Enhanced Q9UPN6 +ENSG00000213085 CFAP45 testis elongated or late spermatids Medium Enhanced Q9UL16 +ENSG00000213185 FAM24B testis cells in seminiferous ducts High Supported Q8N5W8 +ENSG00000213199 ASIC3 testis cells in seminiferous ducts Low Enhanced Q9UHC3 +ENSG00000213214 ARHGEF35 epididymis glandular cells Medium Supported A5YM69 +ENSG00000213214 ARHGEF35 prostate glandular cells Medium Supported A5YM69 +ENSG00000213214 ARHGEF35 seminal vesicle glandular cells Medium Supported A5YM69 +ENSG00000213214 ARHGEF35 testis Leydig cells Low Supported A5YM69 +ENSG00000213462 ERV3-1 epididymis glandular cells Medium Enhanced Q14264 +ENSG00000213462 ERV3-1 prostate glandular cells Low Enhanced Q14264 +ENSG00000213462 ERV3-1 testis cells in seminiferous ducts High Enhanced Q14264 +ENSG00000213462 ERV3-1 testis Leydig cells Medium Enhanced Q14264 +ENSG00000213465 ARL2 epididymis glandular cells High Supported P36404 +ENSG00000213465 ARL2 prostate glandular cells Medium Supported P36404 +ENSG00000213465 ARL2 seminal vesicle glandular cells Medium Supported P36404 +ENSG00000213465 ARL2 testis cells in seminiferous ducts High Supported P36404 +ENSG00000213465 ARL2 testis Leydig cells Medium Supported P36404 +ENSG00000213471 TTLL13P testis Leydig cells Medium Enhanced A6NNM8 +ENSG00000213516 RBMXL1 epididymis glandular cells High Supported Q96E39 +ENSG00000213516 RBMXL1 prostate glandular cells Medium Supported Q96E39 +ENSG00000213516 RBMXL1 seminal vesicle glandular cells Medium Supported Q96E39 +ENSG00000213516 RBMXL1 testis cells in seminiferous ducts High Supported Q96E39 +ENSG00000213516 RBMXL1 testis Leydig cells High Supported Q96E39 +ENSG00000213551 DNAJC9 epididymis glandular cells Medium Enhanced Q8WXX5 +ENSG00000213551 DNAJC9 prostate glandular cells Medium Enhanced Q8WXX5 +ENSG00000213551 DNAJC9 seminal vesicle glandular cells High Enhanced Q8WXX5 +ENSG00000213551 DNAJC9 testis cells in seminiferous ducts High Enhanced Q8WXX5 +ENSG00000213551 DNAJC9 testis Leydig cells Medium Enhanced Q8WXX5 +ENSG00000213585 VDAC1 epididymis glandular cells Medium Supported P21796 +ENSG00000213585 VDAC1 prostate glandular cells Medium Supported P21796 +ENSG00000213585 VDAC1 seminal vesicle glandular cells Medium Supported P21796 +ENSG00000213585 VDAC1 testis cells in seminiferous ducts Medium Supported P21796 +ENSG00000213585 VDAC1 testis Leydig cells High Supported P21796 +ENSG00000213614 HEXA epididymis glandular cells Low Supported P06865 +ENSG00000213614 HEXA prostate glandular cells High Supported P06865 +ENSG00000213614 HEXA seminal vesicle glandular cells Medium Supported P06865 +ENSG00000213614 HEXA testis cells in seminiferous ducts Medium Supported P06865 +ENSG00000213614 HEXA testis Leydig cells Medium Supported P06865 +ENSG00000213639 PPP1CB epididymis glandular cells Medium Supported P62140 +ENSG00000213639 PPP1CB prostate glandular cells Low Supported P62140 +ENSG00000213639 PPP1CB seminal vesicle glandular cells Medium Supported P62140 +ENSG00000213639 PPP1CB testis cells in seminiferous ducts Medium Supported P62140 +ENSG00000213639 PPP1CB testis Leydig cells Medium Supported P62140 +ENSG00000213648 SULT1A4 seminal vesicle glandular cells Low Supported P0DMN0 +ENSG00000213648 SULT1A4 testis Leydig cells Low Supported P0DMN0 +ENSG00000213689 TREX1 epididymis glandular cells Medium Supported Q9NSU2 +ENSG00000213689 TREX1 prostate glandular cells Medium Supported Q9NSU2 +ENSG00000213689 TREX1 seminal vesicle glandular cells Medium Supported Q9NSU2 +ENSG00000213689 TREX1 testis cells in seminiferous ducts Medium Supported Q9NSU2 +ENSG00000213689 TREX1 testis Leydig cells Medium Supported Q9NSU2 +ENSG00000213714 FAM209B testis elongated or late spermatids High Enhanced Q5JX69 +ENSG00000213714 FAM209B testis Leydig cells Low Enhanced Q5JX69 +ENSG00000213714 FAM209B testis pachytene spermatocytes Low Enhanced Q5JX69 +ENSG00000213714 FAM209B testis preleptotene spermatocytes Low Enhanced Q5JX69 +ENSG00000213714 FAM209B testis round or early spermatids High Enhanced Q5JX69 +ENSG00000213719 CLIC1 epididymis glandular cells Low Enhanced NA +ENSG00000213719 CLIC1 prostate glandular cells Medium Enhanced NA +ENSG00000213719 CLIC1 seminal vesicle glandular cells Medium Enhanced NA +ENSG00000213719 CLIC1 testis cells in seminiferous ducts Low Enhanced NA +ENSG00000213719 CLIC1 testis Leydig cells Medium Enhanced NA +ENSG00000213762 ZNF134 epididymis glandular cells High Supported P52741 +ENSG00000213762 ZNF134 prostate glandular cells Medium Supported P52741 +ENSG00000213762 ZNF134 seminal vesicle glandular cells Medium Supported P52741 +ENSG00000213762 ZNF134 testis cells in seminiferous ducts Medium Supported P52741 +ENSG00000213762 ZNF134 testis Leydig cells Medium Supported P52741 +ENSG00000213930 GALT epididymis glandular cells Medium Enhanced P07902 +ENSG00000213930 GALT prostate glandular cells Medium Enhanced P07902 +ENSG00000213930 GALT seminal vesicle glandular cells Medium Enhanced P07902 +ENSG00000213930 GALT testis cells in seminiferous ducts Low Enhanced P07902 +ENSG00000213930 GALT testis Leydig cells High Enhanced P07902 +ENSG00000214107 MAGEB1 testis cells in seminiferous ducts Medium Enhanced P43366 +ENSG00000214114 MYCBP epididymis glandular cells High Supported Q99417 +ENSG00000214114 MYCBP prostate glandular cells Medium Supported Q99417 +ENSG00000214114 MYCBP seminal vesicle glandular cells High Supported Q99417 +ENSG00000214114 MYCBP testis cells in seminiferous ducts High Supported Q99417 +ENSG00000214114 MYCBP testis Leydig cells Low Supported Q99417 +ENSG00000214300 SPDYE3 testis cells in seminiferous ducts Medium Supported A6NKU9 +ENSG00000214300 SPDYE3 testis elongated or late spermatids High Supported A6NKU9 +ENSG00000214300 SPDYE3 testis round or early spermatids Medium Supported A6NKU9 +ENSG00000214435 AS3MT testis Leydig cells High Enhanced Q9HBK9 +ENSG00000214753 HNRNPUL2 epididymis glandular cells Medium Enhanced Q1KMD3 +ENSG00000214753 HNRNPUL2 prostate glandular cells Medium Enhanced Q1KMD3 +ENSG00000214753 HNRNPUL2 seminal vesicle glandular cells Medium Enhanced Q1KMD3 +ENSG00000214753 HNRNPUL2 testis cells in seminiferous ducts Medium Enhanced Q1KMD3 +ENSG00000214753 HNRNPUL2 testis Leydig cells Medium Enhanced Q1KMD3 +ENSG00000214944 ARHGEF28 epididymis glandular cells Medium Enhanced Q8N1W1 +ENSG00000214944 ARHGEF28 seminal vesicle glandular cells Low Enhanced Q8N1W1 +ENSG00000214944 ARHGEF28 testis cells in seminiferous ducts Low Enhanced Q8N1W1 +ENSG00000214944 ARHGEF28 testis Leydig cells Low Enhanced Q8N1W1 +ENSG00000215021 PHB2 epididymis glandular cells Low Supported Q99623 +ENSG00000215021 PHB2 prostate glandular cells Medium Supported Q99623 +ENSG00000215021 PHB2 seminal vesicle glandular cells High Supported Q99623 +ENSG00000215021 PHB2 testis cells in seminiferous ducts Low Supported Q99623 +ENSG00000215021 PHB2 testis Leydig cells High Supported Q99623 +ENSG00000215029 TCP11X2 testis elongated or late spermatids High Supported Q5H9J9 +ENSG00000215029 TCP11X2 testis round or early spermatids Medium Supported Q5H9J9 +ENSG00000215186 GOLGA6B testis elongated or late spermatids High Supported A6NDN3 +ENSG00000215186 GOLGA6B testis round or early spermatids High Supported A6NDN3 +ENSG00000215186 GOLGA6B testis spermatogonia High Supported A6NDN3 +ENSG00000215217 C5orf49 testis cells in seminiferous ducts Low Enhanced A4QMS7 +ENSG00000215217 C5orf49 testis Leydig cells Low Enhanced A4QMS7 +ENSG00000215269 GAGE12G testis cells in seminiferous ducts High Supported P0CL81 +ENSG00000215274 GAGE10 testis pachytene spermatocytes Low Supported A6NGK3 +ENSG00000215274 GAGE10 testis preleptotene spermatocytes High Supported A6NGK3 +ENSG00000215274 GAGE10 testis spermatogonia High Supported A6NGK3 +ENSG00000215301 DDX3X epididymis glandular cells High Supported O00571 +ENSG00000215301 DDX3X prostate glandular cells High Supported O00571 +ENSG00000215301 DDX3X seminal vesicle glandular cells Medium Supported O00571 +ENSG00000215301 DDX3X testis cells in seminiferous ducts Medium Supported O00571 +ENSG00000215301 DDX3X testis Leydig cells Medium Supported O00571 +ENSG00000216649 GAGE12E testis cells in seminiferous ducts High Supported NA +ENSG00000216649 GAGE12E testis pachytene spermatocytes Low Supported NA +ENSG00000216649 GAGE12E testis preleptotene spermatocytes High Supported NA +ENSG00000216649 GAGE12E testis spermatogonia High Supported NA +ENSG00000221900 POM121L12 testis elongated or late spermatids High Enhanced Q8N7R1 +ENSG00000221900 POM121L12 testis Leydig cells Low Enhanced Q8N7R1 +ENSG00000221900 POM121L12 testis pachytene spermatocytes High Enhanced Q8N7R1 +ENSG00000221900 POM121L12 testis round or early spermatids High Enhanced Q8N7R1 +ENSG00000221978 CCNL2 epididymis glandular cells Medium Supported Q96S94 +ENSG00000221978 CCNL2 prostate glandular cells Medium Supported Q96S94 +ENSG00000221978 CCNL2 seminal vesicle glandular cells Medium Supported Q96S94 +ENSG00000221978 CCNL2 testis cells in seminiferous ducts Medium Supported Q96S94 +ENSG00000221978 CCNL2 testis Leydig cells Medium Supported Q96S94 +ENSG00000221983 UBA52 epididymis glandular cells Medium Supported P62987 +ENSG00000221983 UBA52 prostate glandular cells High Supported P62987 +ENSG00000221983 UBA52 seminal vesicle glandular cells Medium Supported P62987 +ENSG00000221983 UBA52 testis cells in seminiferous ducts High Supported P62987 +ENSG00000221983 UBA52 testis Leydig cells Medium Supported P62987 +ENSG00000221994 ZNF630 epididymis glandular cells High Supported Q2M218 +ENSG00000221994 ZNF630 prostate glandular cells High Supported Q2M218 +ENSG00000221994 ZNF630 seminal vesicle glandular cells Medium Supported Q2M218 +ENSG00000221994 ZNF630 testis cells in seminiferous ducts High Supported Q2M218 +ENSG00000221994 ZNF630 testis Leydig cells Medium Supported Q2M218 +ENSG00000224089 CT47A10 testis cells in seminiferous ducts Medium Supported NA +ENSG00000224659 GAGE12J testis cells in seminiferous ducts High Supported A6NER3 +ENSG00000224659 GAGE12J testis pachytene spermatocytes Low Supported A6NER3 +ENSG00000224659 GAGE12J testis preleptotene spermatocytes High Supported A6NER3 +ENSG00000224659 GAGE12J testis spermatogonia High Supported A6NER3 +ENSG00000224902 GAGE12H testis cells in seminiferous ducts High Supported A6NDE8 +ENSG00000224902 GAGE12H testis pachytene spermatocytes Low Supported A6NDE8 +ENSG00000224902 GAGE12H testis preleptotene spermatocytes High Supported A6NDE8 +ENSG00000224902 GAGE12H testis spermatogonia High Supported A6NDE8 +ENSG00000225921 NOL7 epididymis glandular cells Medium Supported Q9UMY1 +ENSG00000225921 NOL7 prostate glandular cells Low Supported Q9UMY1 +ENSG00000225921 NOL7 seminal vesicle glandular cells Low Supported Q9UMY1 +ENSG00000225921 NOL7 testis cells in seminiferous ducts Low Supported Q9UMY1 +ENSG00000225921 NOL7 testis Leydig cells Medium Supported Q9UMY1 +ENSG00000226023 CT47A6 testis cells in seminiferous ducts Medium Supported NA +ENSG00000226174 TEX22 testis cells in seminiferous ducts Medium Enhanced C9J3V5 +ENSG00000226372 DCAF8L1 testis cells in seminiferous ducts Low Enhanced A6NGE4 +ENSG00000226600 CT47A9 testis cells in seminiferous ducts Medium Supported NA +ENSG00000226685 CT47A12 testis cells in seminiferous ducts Medium Supported NA +ENSG00000226929 CT47A11 testis cells in seminiferous ducts Medium Supported NA +ENSG00000226941 RBMY1J testis pachytene spermatocytes High Supported NA +ENSG00000226941 RBMY1J testis preleptotene spermatocytes High Supported NA +ENSG00000226941 RBMY1J testis round or early spermatids High Supported NA +ENSG00000226941 RBMY1J testis spermatogonia High Supported NA +ENSG00000227234 SPANXB1 testis cells in seminiferous ducts Medium Supported Q9NS25 +ENSG00000227345 PARG epididymis glandular cells Medium Enhanced Q86W56 +ENSG00000227345 PARG prostate glandular cells Low Enhanced Q86W56 +ENSG00000227345 PARG seminal vesicle glandular cells Low Enhanced Q86W56 +ENSG00000227345 PARG testis cells in seminiferous ducts Medium Enhanced Q86W56 +ENSG00000227345 PARG testis Leydig cells Low Enhanced Q86W56 +ENSG00000227488 GAGE12D testis cells in seminiferous ducts High Supported NA +ENSG00000227488 GAGE12D testis pachytene spermatocytes Low Supported NA +ENSG00000227488 GAGE12D testis preleptotene spermatocytes High Supported NA +ENSG00000227488 GAGE12D testis spermatogonia High Supported NA +ENSG00000228517 CT47A7 testis cells in seminiferous ducts Medium Supported NA +ENSG00000228836 CT45A5 testis pachytene spermatocytes High Supported P0DMU8 +ENSG00000228836 CT45A5 testis preleptotene spermatocytes Medium Supported P0DMU8 +ENSG00000228836 CT45A5 testis spermatogonia High Supported P0DMU8 +ENSG00000228927 TSPY3 testis preleptotene spermatocytes High Supported P0CV98 +ENSG00000228927 TSPY3 testis spermatogonia High Supported P0CV98 +ENSG00000229549 TSPY8 testis preleptotene spermatocytes High Supported P0CW00 +ENSG00000229549 TSPY8 testis spermatogonia High Supported P0CW00 +ENSG00000230347 CT47A8 testis cells in seminiferous ducts Medium Supported NA +ENSG00000230594 CT47A4 testis cells in seminiferous ducts Medium Supported NA +ENSG00000230797 YY2 testis Leydig cells Low Enhanced O15391 +ENSG00000230797 YY2 testis pachytene spermatocytes Medium Enhanced O15391 +ENSG00000230797 YY2 testis peritubular cells High Enhanced O15391 +ENSG00000230797 YY2 testis sertoli cells High Enhanced O15391 +ENSG00000230873 STMND1 testis Leydig cells Low Enhanced H3BQB6 +ENSG00000231389 HLA-DPA1 testis cells in seminiferous ducts Low Enhanced J3KQ99 +ENSG00000233803 TSPY4 testis preleptotene spermatocytes High Supported P0CV99 +ENSG00000233803 TSPY4 testis spermatogonia High Supported P0CV99 +ENSG00000233822 HIST1H2BN epididymis glandular cells High Supported Q99877 +ENSG00000233822 HIST1H2BN prostate glandular cells High Supported Q99877 +ENSG00000233822 HIST1H2BN seminal vesicle glandular cells High Supported Q99877 +ENSG00000233822 HIST1H2BN testis cells in seminiferous ducts High Supported Q99877 +ENSG00000233822 HIST1H2BN testis Leydig cells High Supported Q99877 +ENSG00000234068 PAGE2 testis cells in seminiferous ducts Low Supported Q7Z2X7 +ENSG00000234289 H2BFS epididymis glandular cells High Supported P57053 +ENSG00000234289 H2BFS prostate glandular cells High Supported P57053 +ENSG00000234289 H2BFS seminal vesicle glandular cells High Supported P57053 +ENSG00000234289 H2BFS testis cells in seminiferous ducts High Supported P57053 +ENSG00000234289 H2BFS testis Leydig cells High Supported P57053 +ENSG00000234414 RBMY1A1 testis pachytene spermatocytes High Supported P0DJD3 +ENSG00000234414 RBMY1A1 testis preleptotene spermatocytes High Supported P0DJD3 +ENSG00000234414 RBMY1A1 testis round or early spermatids High Supported P0DJD3 +ENSG00000234414 RBMY1A1 testis spermatogonia High Supported P0DJD3 +ENSG00000234719 NPIPB2 epididymis glandular cells Medium Supported F8VY45 +ENSG00000234719 NPIPB2 prostate glandular cells Medium Supported F8VY45 +ENSG00000234719 NPIPB2 seminal vesicle glandular cells Medium Supported F8VY45 +ENSG00000234719 NPIPB2 testis elongated or late spermatids Medium Supported F8VY45 +ENSG00000234719 NPIPB2 testis Leydig cells Medium Supported F8VY45 +ENSG00000234719 NPIPB2 testis pachytene spermatocytes High Supported F8VY45 +ENSG00000234719 NPIPB2 testis peritubular cells Low Supported F8VY45 +ENSG00000234719 NPIPB2 testis preleptotene spermatocytes Medium Supported F8VY45 +ENSG00000234719 NPIPB2 testis round or early spermatids High Supported F8VY45 +ENSG00000234719 NPIPB2 testis sertoli cells High Supported F8VY45 +ENSG00000234719 NPIPB2 testis spermatogonia High Supported F8VY45 +ENSG00000234745 HLA-B epididymis glandular cells Low Enhanced P01889 +ENSG00000234745 HLA-B prostate glandular cells High Enhanced P01889 +ENSG00000234745 HLA-B seminal vesicle glandular cells Low Enhanced P01889 +ENSG00000234745 HLA-B testis cells in seminiferous ducts Medium Enhanced P01889 +ENSG00000234745 HLA-B testis Leydig cells Medium Enhanced P01889 +ENSG00000235034 C19orf81 testis elongated or late spermatids High Enhanced C9J6K1 +ENSG00000235034 C19orf81 testis Leydig cells Low Enhanced C9J6K1 +ENSG00000235034 C19orf81 testis pachytene spermatocytes Low Enhanced C9J6K1 +ENSG00000235034 C19orf81 testis preleptotene spermatocytes Medium Enhanced C9J6K1 +ENSG00000235034 C19orf81 testis round or early spermatids Low Enhanced C9J6K1 +ENSG00000235034 C19orf81 testis spermatogonia High Enhanced C9J6K1 +ENSG00000236126 CT47A3 testis cells in seminiferous ducts Medium Supported NA +ENSG00000236362 GAGE12F testis cells in seminiferous ducts High Supported P0CL80 +ENSG00000236362 GAGE12F testis pachytene spermatocytes Low Supported P0CL80 +ENSG00000236362 GAGE12F testis preleptotene spermatocytes High Supported P0CL80 +ENSG00000236362 GAGE12F testis spermatogonia High Supported P0CL80 +ENSG00000236371 CT47A1 testis cells in seminiferous ducts Medium Supported NA +ENSG00000236424 TSPY10 testis preleptotene spermatocytes High Supported P0CW01 +ENSG00000236424 TSPY10 testis spermatogonia High Supported P0CW01 +ENSG00000236446 CT47B1 testis cells in seminiferous ducts Medium Supported P0C2W7 +ENSG00000237649 KIFC1 epididymis glandular cells Low Supported A0A087X1W5 +ENSG00000237649 KIFC1 seminal vesicle glandular cells Low Supported A0A087X1W5 +ENSG00000237649 KIFC1 testis cells in seminiferous ducts High Supported A0A087X1W5 +ENSG00000237671 GAGE12C testis cells in seminiferous ducts High Supported NA +ENSG00000237671 GAGE12C testis pachytene spermatocytes Low Supported NA +ENSG00000237671 GAGE12C testis preleptotene spermatocytes High Supported NA +ENSG00000237671 GAGE12C testis spermatogonia High Supported NA +ENSG00000237957 CT47A5 testis cells in seminiferous ducts Medium Supported NA +ENSG00000238083 LRRC37A2 testis elongated or late spermatids High Supported A6NM11 +ENSG00000238083 LRRC37A2 testis pachytene spermatocytes Low Supported A6NM11 +ENSG00000238083 LRRC37A2 testis preleptotene spermatocytes Low Supported A6NM11 +ENSG00000238083 LRRC37A2 testis round or early spermatids High Supported A6NM11 +ENSG00000238227 C9orf69 epididymis glandular cells High Supported H0YL14 +ENSG00000238227 C9orf69 prostate glandular cells High Supported H0YL14 +ENSG00000238227 C9orf69 seminal vesicle glandular cells High Supported H0YL14 +ENSG00000238227 C9orf69 testis cells in seminiferous ducts Medium Supported H0YL14 +ENSG00000238227 C9orf69 testis Leydig cells High Supported H0YL14 +ENSG00000238269 PAGE2B testis cells in seminiferous ducts Low Supported Q5JRK9 +ENSG00000239264 TXNDC5 epididymis glandular cells Medium Enhanced Q8NBS9 +ENSG00000239264 TXNDC5 seminal vesicle glandular cells Medium Enhanced Q8NBS9 +ENSG00000239264 TXNDC5 testis cells in seminiferous ducts Medium Enhanced Q8NBS9 +ENSG00000239264 TXNDC5 testis Leydig cells Medium Enhanced Q8NBS9 +ENSG00000239306 RBM14 epididymis glandular cells Medium Supported Q96PK6 +ENSG00000239306 RBM14 prostate glandular cells High Supported Q96PK6 +ENSG00000239306 RBM14 seminal vesicle glandular cells Medium Supported Q96PK6 +ENSG00000239306 RBM14 testis cells in seminiferous ducts High Supported Q96PK6 +ENSG00000239306 RBM14 testis Leydig cells Low Supported Q96PK6 +ENSG00000239672 NME1 epididymis glandular cells Medium Supported P15531 +ENSG00000239672 NME1 prostate glandular cells Medium Supported P15531 +ENSG00000239672 NME1 seminal vesicle glandular cells Medium Supported P15531 +ENSG00000239672 NME1 testis cells in seminiferous ducts Medium Supported P15531 +ENSG00000239672 NME1 testis Leydig cells Medium Supported P15531 +ENSG00000239900 ADSL epididymis glandular cells Medium Enhanced P30566 +ENSG00000239900 ADSL prostate glandular cells Medium Enhanced P30566 +ENSG00000239900 ADSL seminal vesicle glandular cells Medium Enhanced P30566 +ENSG00000239900 ADSL testis cells in seminiferous ducts High Enhanced P30566 +ENSG00000239900 ADSL testis Leydig cells Medium Enhanced P30566 +ENSG00000240065 PSMB9 prostate glandular cells Low Enhanced NA +ENSG00000240065 PSMB9 testis cells in seminiferous ducts Low Enhanced NA +ENSG00000240065 PSMB9 testis Leydig cells Low Enhanced NA +ENSG00000240303 ACAD11 testis Leydig cells Low Enhanced Q709F0 +ENSG00000240682 ISY1 epididymis glandular cells High Supported Q9ULR0 +ENSG00000240682 ISY1 prostate glandular cells High Supported Q9ULR0 +ENSG00000240682 ISY1 seminal vesicle glandular cells High Supported Q9ULR0 +ENSG00000240682 ISY1 testis cells in seminiferous ducts High Supported Q9ULR0 +ENSG00000240682 ISY1 testis Leydig cells High Supported Q9ULR0 +ENSG00000241476 SSX2 testis pachytene spermatocytes Low Enhanced NA +ENSG00000241476 SSX2 testis preleptotene spermatocytes Medium Enhanced NA +ENSG00000241476 SSX2 testis spermatogonia High Enhanced NA +ENSG00000241837 ATP5O epididymis glandular cells Medium Enhanced P48047 +ENSG00000241837 ATP5O prostate glandular cells High Enhanced P48047 +ENSG00000241837 ATP5O seminal vesicle glandular cells High Enhanced P48047 +ENSG00000241837 ATP5O testis cells in seminiferous ducts Medium Enhanced P48047 +ENSG00000241837 ATP5O testis Leydig cells High Enhanced P48047 +ENSG00000242110 AMACR epididymis glandular cells Low Enhanced Q9UHK6 +ENSG00000242110 AMACR prostate glandular cells Low Enhanced Q9UHK6 +ENSG00000242110 AMACR testis cells in seminiferous ducts Low Enhanced Q9UHK6 +ENSG00000242265 PEG10 testis cells in seminiferous ducts Low Enhanced Q86TG7 +ENSG00000242362 CT47A2 testis cells in seminiferous ducts Medium Supported NA +ENSG00000242372 EIF6 epididymis glandular cells Medium Enhanced P56537 +ENSG00000242372 EIF6 prostate glandular cells Medium Enhanced P56537 +ENSG00000242372 EIF6 testis cells in seminiferous ducts High Enhanced P56537 +ENSG00000242372 EIF6 testis Leydig cells Medium Enhanced P56537 +ENSG00000242389 RBMY1E testis pachytene spermatocytes High Supported A6NEQ0 +ENSG00000242389 RBMY1E testis preleptotene spermatocytes High Supported A6NEQ0 +ENSG00000242389 RBMY1E testis round or early spermatids High Supported A6NEQ0 +ENSG00000242389 RBMY1E testis spermatogonia High Supported A6NEQ0 +ENSG00000242485 MRPL20 epididymis glandular cells Medium Supported Q9BYC9 +ENSG00000242485 MRPL20 prostate glandular cells Medium Supported Q9BYC9 +ENSG00000242485 MRPL20 seminal vesicle glandular cells Medium Supported Q9BYC9 +ENSG00000242485 MRPL20 testis cells in seminiferous ducts Medium Supported Q9BYC9 +ENSG00000242485 MRPL20 testis Leydig cells High Supported Q9BYC9 +ENSG00000242802 AP5Z1 epididymis glandular cells High Supported O43299 +ENSG00000242802 AP5Z1 prostate glandular cells High Supported O43299 +ENSG00000242802 AP5Z1 seminal vesicle glandular cells Medium Supported O43299 +ENSG00000242802 AP5Z1 testis cells in seminiferous ducts Medium Supported O43299 +ENSG00000242802 AP5Z1 testis Leydig cells Medium Supported O43299 +ENSG00000242866 STRC testis cells in seminiferous ducts Medium Enhanced Q7RTU9 +ENSG00000242875 RBMY1B testis pachytene spermatocytes High Supported A6NDE4 +ENSG00000242875 RBMY1B testis preleptotene spermatocytes High Supported A6NDE4 +ENSG00000242875 RBMY1B testis round or early spermatids High Supported A6NDE4 +ENSG00000242875 RBMY1B testis spermatogonia High Supported A6NDE4 +ENSG00000243279 PRAF2 epididymis glandular cells High Enhanced O60831 +ENSG00000243279 PRAF2 prostate glandular cells Low Enhanced O60831 +ENSG00000243279 PRAF2 seminal vesicle glandular cells Medium Enhanced O60831 +ENSG00000243279 PRAF2 testis cells in seminiferous ducts Medium Enhanced O60831 +ENSG00000243279 PRAF2 testis Leydig cells Medium Enhanced O60831 +ENSG00000243649 CFB prostate glandular cells Low Supported H7C526 +ENSG00000243710 CFAP57 testis round or early spermatids Medium Enhanced Q96MR6 +ENSG00000243927 MRPS6 epididymis glandular cells Medium Supported P82932 +ENSG00000243927 MRPS6 prostate glandular cells High Supported P82932 +ENSG00000243927 MRPS6 seminal vesicle glandular cells High Supported P82932 +ENSG00000243927 MRPS6 testis cells in seminiferous ducts Medium Supported P82932 +ENSG00000243927 MRPS6 testis Leydig cells High Supported P82932 +ENSG00000243955 GSTA1 epididymis glandular cells Low Supported P08263 +ENSG00000243955 GSTA1 testis cells in seminiferous ducts Medium Supported P08263 +ENSG00000243955 GSTA1 testis Leydig cells High Supported P08263 +ENSG00000243978 RGAG1 testis Leydig cells Medium Enhanced Q8NET4 +ENSG00000243978 RGAG1 testis sertoli cells High Enhanced Q8NET4 +ENSG00000244005 NFS1 epididymis glandular cells Medium Enhanced Q9Y697 +ENSG00000244005 NFS1 prostate glandular cells Medium Enhanced Q9Y697 +ENSG00000244005 NFS1 seminal vesicle glandular cells Medium Enhanced Q9Y697 +ENSG00000244005 NFS1 testis cells in seminiferous ducts High Enhanced Q9Y697 +ENSG00000244005 NFS1 testis Leydig cells High Enhanced Q9Y697 +ENSG00000244038 DDOST epididymis glandular cells High Supported P39656 +ENSG00000244038 DDOST prostate glandular cells Medium Supported P39656 +ENSG00000244038 DDOST seminal vesicle glandular cells High Supported P39656 +ENSG00000244038 DDOST testis cells in seminiferous ducts Medium Supported P39656 +ENSG00000244038 DDOST testis Leydig cells Medium Supported P39656 +ENSG00000244067 GSTA2 epididymis glandular cells Low Supported P09210 +ENSG00000244067 GSTA2 testis cells in seminiferous ducts Medium Supported P09210 +ENSG00000244067 GSTA2 testis Leydig cells Medium Supported P09210 +ENSG00000244274 DBNDD2 testis cells in seminiferous ducts Medium Enhanced Q9BQY9 +ENSG00000244274 DBNDD2 testis Leydig cells Low Enhanced Q9BQY9 +ENSG00000244395 RBMY1D testis cells in seminiferous ducts Medium Supported P0C7P1 +ENSG00000244462 RBM12 epididymis glandular cells Medium Enhanced Q9NTZ6 +ENSG00000244462 RBM12 prostate glandular cells High Enhanced Q9NTZ6 +ENSG00000244462 RBM12 seminal vesicle glandular cells Medium Enhanced Q9NTZ6 +ENSG00000244462 RBM12 testis cells in seminiferous ducts High Enhanced Q9NTZ6 +ENSG00000244462 RBM12 testis Leydig cells Medium Enhanced Q9NTZ6 +ENSG00000246705 H2AFJ epididymis glandular cells Medium Supported Q9BTM1 +ENSG00000246705 H2AFJ prostate glandular cells Low Supported Q9BTM1 +ENSG00000246705 H2AFJ seminal vesicle glandular cells Medium Supported Q9BTM1 +ENSG00000246705 H2AFJ testis cells in seminiferous ducts High Supported Q9BTM1 +ENSG00000246705 H2AFJ testis Leydig cells Low Supported Q9BTM1 +ENSG00000247077 PGAM5 epididymis glandular cells Medium Enhanced Q96HS1 +ENSG00000247077 PGAM5 prostate glandular cells Medium Enhanced Q96HS1 +ENSG00000247077 PGAM5 seminal vesicle glandular cells Medium Enhanced Q96HS1 +ENSG00000247077 PGAM5 testis cells in seminiferous ducts Medium Enhanced Q96HS1 +ENSG00000247077 PGAM5 testis Leydig cells Medium Enhanced Q96HS1 +ENSG00000248098 BCKDHA epididymis glandular cells Medium Supported P12694 +ENSG00000248098 BCKDHA prostate glandular cells High Supported P12694 +ENSG00000248098 BCKDHA seminal vesicle glandular cells High Supported P12694 +ENSG00000248098 BCKDHA testis cells in seminiferous ducts High Supported P12694 +ENSG00000248098 BCKDHA testis Leydig cells High Supported P12694 +ENSG00000248099 INSL3 testis Leydig cells High Enhanced P51460 +ENSG00000248144 ADH1C epididymis glandular cells Medium Supported P00326 +ENSG00000248144 ADH1C seminal vesicle glandular cells Medium Supported P00326 +ENSG00000248144 ADH1C testis cells in seminiferous ducts Low Supported P00326 +ENSG00000248144 ADH1C testis Leydig cells Low Supported P00326 +ENSG00000248485 PCP4L1 epididymis glandular cells Medium Enhanced A6NKN8 +ENSG00000248485 PCP4L1 prostate glandular cells Medium Enhanced A6NKN8 +ENSG00000248485 PCP4L1 testis cells in seminiferous ducts High Enhanced A6NKN8 +ENSG00000249242 TMEM150C epididymis glandular cells High Enhanced B9EJG8 +ENSG00000250423 KIAA1210 testis elongated or late spermatids High Enhanced Q9ULL0 +ENSG00000250423 KIAA1210 testis pachytene spermatocytes High Enhanced Q9ULL0 +ENSG00000250423 KIAA1210 testis preleptotene spermatocytes Low Enhanced Q9ULL0 +ENSG00000250423 KIAA1210 testis round or early spermatids High Enhanced Q9ULL0 +ENSG00000250423 KIAA1210 testis sertoli cells High Enhanced Q9ULL0 +ENSG00000250479 CHCHD10 epididymis glandular cells Medium Enhanced NA +ENSG00000250479 CHCHD10 prostate glandular cells Low Enhanced NA +ENSG00000250479 CHCHD10 seminal vesicle glandular cells Medium Enhanced NA +ENSG00000251322 SHANK3 epididymis glandular cells Medium Enhanced A0A0U1RR93 +ENSG00000253729 PRKDC epididymis glandular cells High Supported P78527 +ENSG00000253729 PRKDC prostate glandular cells High Supported P78527 +ENSG00000253729 PRKDC seminal vesicle glandular cells High Supported P78527 +ENSG00000253729 PRKDC testis cells in seminiferous ducts High Supported P78527 +ENSG00000253729 PRKDC testis Leydig cells High Supported P78527 +ENSG00000254087 LYN prostate glandular cells Low Enhanced P07948 +ENSG00000254087 LYN seminal vesicle glandular cells Low Enhanced P07948 +ENSG00000254402 LRRC24 prostate glandular cells High Enhanced Q50LG9 +ENSG00000254402 LRRC24 testis Leydig cells Low Enhanced Q50LG9 +ENSG00000254636 ARMS2 testis elongated or late spermatids High Enhanced P0C7Q2 +ENSG00000254772 EEF1G epididymis glandular cells Medium Enhanced P26641 +ENSG00000254772 EEF1G prostate glandular cells Low Enhanced P26641 +ENSG00000254772 EEF1G seminal vesicle glandular cells Medium Enhanced P26641 +ENSG00000254772 EEF1G testis cells in seminiferous ducts Medium Enhanced P26641 +ENSG00000254772 EEF1G testis Leydig cells Medium Enhanced P26641 +ENSG00000255112 CHMP1B epididymis glandular cells Medium Enhanced Q7LBR1 +ENSG00000255112 CHMP1B prostate glandular cells Medium Enhanced Q7LBR1 +ENSG00000255112 CHMP1B seminal vesicle glandular cells Low Enhanced Q7LBR1 +ENSG00000255112 CHMP1B testis cells in seminiferous ducts Medium Enhanced Q7LBR1 +ENSG00000255112 CHMP1B testis Leydig cells Medium Enhanced Q7LBR1 +ENSG00000256269 HMBS epididymis glandular cells Medium Enhanced A0A1W2PNU5 +ENSG00000256269 HMBS prostate glandular cells Medium Enhanced A0A1W2PNU5 +ENSG00000256269 HMBS seminal vesicle glandular cells Medium Enhanced A0A1W2PNU5 +ENSG00000256269 HMBS testis cells in seminiferous ducts Medium Enhanced A0A1W2PNU5 +ENSG00000256269 HMBS testis Leydig cells Medium Enhanced A0A1W2PNU5 +ENSG00000257335 MGAM epididymis glandular cells High Enhanced O43451 +ENSG00000257335 MGAM seminal vesicle glandular cells Low Enhanced O43451 +ENSG00000257335 MGAM testis cells in seminiferous ducts Low Enhanced O43451 +ENSG00000257727 CNPY2 epididymis glandular cells High Supported Q9Y2B0 +ENSG00000257727 CNPY2 prostate glandular cells Medium Supported Q9Y2B0 +ENSG00000257727 CNPY2 seminal vesicle glandular cells Medium Supported Q9Y2B0 +ENSG00000257727 CNPY2 testis cells in seminiferous ducts Medium Supported Q9Y2B0 +ENSG00000257727 CNPY2 testis Leydig cells Medium Supported Q9Y2B0 +ENSG00000258315 C17orf49 epididymis glandular cells High Supported Q8IXM2 +ENSG00000258315 C17orf49 prostate glandular cells High Supported Q8IXM2 +ENSG00000258315 C17orf49 seminal vesicle glandular cells Medium Supported Q8IXM2 +ENSG00000258315 C17orf49 testis cells in seminiferous ducts High Supported Q8IXM2 +ENSG00000258315 C17orf49 testis Leydig cells High Supported Q8IXM2 +ENSG00000258436 RNASE12 epididymis glandular cells High Enhanced Q5GAN4 +ENSG00000258484 SPESP1 testis elongated or late spermatids High Enhanced Q6UW49 +ENSG00000258484 SPESP1 testis round or early spermatids High Enhanced Q6UW49 +ENSG00000258992 TSPY1 testis preleptotene spermatocytes High Supported Q01534 +ENSG00000258992 TSPY1 testis spermatogonia High Supported Q01534 +ENSG00000260230 FRRS1L testis Leydig cells Low Enhanced Q9P0K9 +ENSG00000260287 TBC1D3G testis cells in seminiferous ducts Medium Supported NA +ENSG00000260287 TBC1D3G testis elongated or late spermatids High Supported NA +ENSG00000260287 TBC1D3G testis round or early spermatids High Supported NA +ENSG00000260287 TBC1D3G testis sertoli cells Low Supported NA +ENSG00000260314 MRC1 testis cells in seminiferous ducts Low Enhanced P22897 +ENSG00000260456 C16orf95 testis Leydig cells Low Supported Q9H693 +ENSG00000260456 C16orf95 testis pachytene spermatocytes Medium Supported Q9H693 +ENSG00000260456 C16orf95 testis preleptotene spermatocytes Low Supported Q9H693 +ENSG00000260456 C16orf95 testis round or early spermatids High Supported Q9H693 +ENSG00000261052 SULT1A3 seminal vesicle glandular cells Low Supported P0DMM9 +ENSG00000261857 MIA testis cells in seminiferous ducts Medium Supported Q16674 +ENSG00000262814 MRPL12 epididymis glandular cells High Supported P52815 +ENSG00000262814 MRPL12 prostate glandular cells High Supported P52815 +ENSG00000262814 MRPL12 seminal vesicle glandular cells High Supported P52815 +ENSG00000262814 MRPL12 testis cells in seminiferous ducts High Supported P52815 +ENSG00000262814 MRPL12 testis Leydig cells High Supported P52815 +ENSG00000263001 GTF2I epididymis glandular cells High Supported P78347 +ENSG00000263001 GTF2I prostate glandular cells Medium Supported P78347 +ENSG00000263001 GTF2I seminal vesicle glandular cells Medium Supported P78347 +ENSG00000263001 GTF2I testis cells in seminiferous ducts Medium Supported P78347 +ENSG00000263001 GTF2I testis Leydig cells Medium Supported P78347 +ENSG00000263465 SRSF8 epididymis glandular cells High Supported Q9BRL6 +ENSG00000263465 SRSF8 prostate glandular cells Medium Supported Q9BRL6 +ENSG00000263465 SRSF8 seminal vesicle glandular cells Medium Supported Q9BRL6 +ENSG00000263465 SRSF8 testis cells in seminiferous ducts High Supported Q9BRL6 +ENSG00000263465 SRSF8 testis Leydig cells High Supported Q9BRL6 +ENSG00000263639 MSMB prostate glandular cells High Enhanced P08118 +ENSG00000263639 MSMB seminal vesicle glandular cells Low Enhanced P08118 +ENSG00000263639 MSMB testis Leydig cells Low Enhanced P08118 +ENSG00000264522 OTUD7B epididymis glandular cells High Supported Q6GQQ9 +ENSG00000264522 OTUD7B prostate glandular cells High Supported Q6GQQ9 +ENSG00000264522 OTUD7B seminal vesicle glandular cells Medium Supported Q6GQQ9 +ENSG00000264522 OTUD7B testis cells in seminiferous ducts High Supported Q6GQQ9 +ENSG00000264522 OTUD7B testis Leydig cells Medium Supported Q6GQQ9 +ENSG00000265241 RBM8A epididymis glandular cells High Supported Q9Y5S9 +ENSG00000265241 RBM8A prostate glandular cells High Supported Q9Y5S9 +ENSG00000265241 RBM8A seminal vesicle glandular cells Medium Supported Q9Y5S9 +ENSG00000265241 RBM8A testis cells in seminiferous ducts High Supported Q9Y5S9 +ENSG00000265241 RBM8A testis Leydig cells Medium Supported Q9Y5S9 +ENSG00000265681 RPL17 epididymis glandular cells Medium Supported P18621 +ENSG00000265681 RPL17 prostate glandular cells Medium Supported P18621 +ENSG00000265681 RPL17 seminal vesicle glandular cells Medium Supported P18621 +ENSG00000265681 RPL17 testis cells in seminiferous ducts Medium Supported P18621 +ENSG00000265681 RPL17 testis Leydig cells Medium Supported P18621 +ENSG00000266967 AARSD1 epididymis glandular cells Low Supported L7N2F4 +ENSG00000266967 AARSD1 prostate glandular cells Low Supported L7N2F4 +ENSG00000266967 AARSD1 testis cells in seminiferous ducts High Supported L7N2F4 +ENSG00000267368 UPK3BL testis Leydig cells Low Supported B0FP48 +ENSG00000267855 NDUFA7 epididymis glandular cells Low Enhanced O95182 +ENSG00000267855 NDUFA7 prostate glandular cells Medium Enhanced O95182 +ENSG00000267855 NDUFA7 seminal vesicle glandular cells Medium Enhanced O95182 +ENSG00000267855 NDUFA7 testis cells in seminiferous ducts Medium Enhanced O95182 +ENSG00000267855 NDUFA7 testis Leydig cells Medium Enhanced O95182 +ENSG00000268447 SSX2B testis pachytene spermatocytes Low Supported NA +ENSG00000268447 SSX2B testis preleptotene spermatocytes Medium Supported NA +ENSG00000268447 SSX2B testis spermatogonia High Supported NA +ENSG00000268629 TEX13A testis cells in seminiferous ducts Medium Enhanced Q9BXU3 +ENSG00000268651 CTAG1A testis pachytene spermatocytes High Enhanced A0A0A0MTT5 +ENSG00000268651 CTAG1A testis preleptotene spermatocytes High Enhanced A0A0A0MTT5 +ENSG00000268651 CTAG1A testis spermatogonia High Enhanced A0A0A0MTT5 +ENSG00000268738 HSFX2 testis cells in seminiferous ducts Medium Supported NA +ENSG00000268861 CTD-2207O23.3 epididymis glandular cells Low Supported A0A087WZG4 +ENSG00000268861 CTD-2207O23.3 testis cells in seminiferous ducts Low Supported A0A087WZG4 +ENSG00000268861 CTD-2207O23.3 testis Leydig cells Low Supported A0A087WZG4 +ENSG00000268940 CT45A1 testis pachytene spermatocytes High Supported Q5HYN5 +ENSG00000268940 CT45A1 testis preleptotene spermatocytes Medium Supported Q5HYN5 +ENSG00000268940 CT45A1 testis spermatogonia High Supported Q5HYN5 +ENSG00000269058 CALR3 testis elongated or late spermatids High Enhanced Q96L12 +ENSG00000269058 CALR3 testis Leydig cells Low Enhanced Q96L12 +ENSG00000269058 CALR3 testis pachytene spermatocytes Medium Enhanced Q96L12 +ENSG00000269058 CALR3 testis preleptotene spermatocytes Medium Enhanced Q96L12 +ENSG00000269058 CALR3 testis round or early spermatids High Enhanced Q96L12 +ENSG00000269058 CALR3 testis sertoli cells Low Enhanced Q96L12 +ENSG00000269058 CALR3 testis spermatogonia Medium Enhanced Q96L12 +ENSG00000269096 CT45A3 testis pachytene spermatocytes High Supported Q8NHU0 +ENSG00000269096 CT45A3 testis preleptotene spermatocytes Medium Supported Q8NHU0 +ENSG00000269096 CT45A3 testis spermatogonia High Supported Q8NHU0 +ENSG00000269586 CT45A10 testis pachytene spermatocytes High Supported P0DMU9 +ENSG00000269586 CT45A10 testis preleptotene spermatocytes Medium Supported P0DMU9 +ENSG00000269586 CT45A10 testis spermatogonia High Supported P0DMU9 +ENSG00000270276 HIST2H4B epididymis glandular cells Low Supported NA +ENSG00000270276 HIST2H4B prostate glandular cells Low Supported NA +ENSG00000270276 HIST2H4B seminal vesicle glandular cells Medium Supported NA +ENSG00000270276 HIST2H4B testis cells in seminiferous ducts Medium Supported NA +ENSG00000270647 TAF15 epididymis glandular cells High Enhanced NA +ENSG00000270647 TAF15 prostate glandular cells Medium Enhanced NA +ENSG00000270647 TAF15 seminal vesicle glandular cells Medium Enhanced NA +ENSG00000270647 TAF15 testis cells in seminiferous ducts High Enhanced NA +ENSG00000270647 TAF15 testis Leydig cells High Enhanced NA +ENSG00000270882 HIST2H4A epididymis glandular cells Low Supported NA +ENSG00000270882 HIST2H4A prostate glandular cells Low Supported NA +ENSG00000270882 HIST2H4A seminal vesicle glandular cells Medium Supported NA +ENSG00000270882 HIST2H4A testis cells in seminiferous ducts Medium Supported NA +ENSG00000270946 CT45A9 testis pachytene spermatocytes High Supported P0DMV2 +ENSG00000270946 CT45A9 testis preleptotene spermatocytes Medium Supported P0DMV2 +ENSG00000270946 CT45A9 testis spermatogonia High Supported P0DMV2 +ENSG00000271449 CT45A2 testis pachytene spermatocytes High Supported Q5DJT8 +ENSG00000271449 CT45A2 testis preleptotene spermatocytes Medium Supported Q5DJT8 +ENSG00000271449 CT45A2 testis spermatogonia High Supported Q5DJT8 +ENSG00000272196 HIST2H2AA4 epididymis glandular cells Medium Supported NA +ENSG00000272196 HIST2H2AA4 prostate glandular cells Low Supported NA +ENSG00000272196 HIST2H2AA4 seminal vesicle glandular cells Medium Supported NA +ENSG00000272196 HIST2H2AA4 testis elongated or late spermatids High Supported NA +ENSG00000272196 HIST2H2AA4 testis pachytene spermatocytes High Supported NA +ENSG00000272196 HIST2H2AA4 testis preleptotene spermatocytes High Supported NA +ENSG00000272196 HIST2H2AA4 testis round or early spermatids High Supported NA +ENSG00000272196 HIST2H2AA4 testis spermatogonia High Supported NA +ENSG00000273542 HIST1H4K epididymis glandular cells Low Supported NA +ENSG00000273542 HIST1H4K prostate glandular cells Low Supported NA +ENSG00000273542 HIST1H4K seminal vesicle glandular cells Medium Supported NA +ENSG00000273542 HIST1H4K testis cells in seminiferous ducts Medium Supported NA +ENSG00000273559 CWC25 epididymis glandular cells High Enhanced NA +ENSG00000273559 CWC25 prostate glandular cells Medium Enhanced NA +ENSG00000273559 CWC25 seminal vesicle glandular cells High Enhanced NA +ENSG00000273559 CWC25 testis cells in seminiferous ducts High Enhanced NA +ENSG00000273559 CWC25 testis Leydig cells Medium Enhanced NA +ENSG00000273604 EPOP testis preleptotene spermatocytes Medium Enhanced NA +ENSG00000273604 EPOP testis spermatogonia High Enhanced NA +ENSG00000273696 CT45A7 testis pachytene spermatocytes High Supported P0DMV0 +ENSG00000273696 CT45A7 testis preleptotene spermatocytes Medium Supported P0DMV0 +ENSG00000273696 CT45A7 testis spermatogonia High Supported P0DMV0 +ENSG00000273703 HIST1H2BM epididymis glandular cells High Supported Q99879 +ENSG00000273703 HIST1H2BM prostate glandular cells High Supported Q99879 +ENSG00000273703 HIST1H2BM seminal vesicle glandular cells High Supported Q99879 +ENSG00000273703 HIST1H2BM testis cells in seminiferous ducts High Supported Q99879 +ENSG00000273703 HIST1H2BM testis Leydig cells High Supported Q99879 +ENSG00000273802 HIST1H2BG epididymis glandular cells High Supported NA +ENSG00000273802 HIST1H2BG prostate glandular cells High Supported NA +ENSG00000273802 HIST1H2BG seminal vesicle glandular cells High Supported NA +ENSG00000273802 HIST1H2BG testis cells in seminiferous ducts High Supported NA +ENSG00000273802 HIST1H2BG testis Leydig cells High Supported NA +ENSG00000273983 HIST1H3G epididymis glandular cells High Supported NA +ENSG00000273983 HIST1H3G prostate glandular cells High Supported NA +ENSG00000273983 HIST1H3G seminal vesicle glandular cells High Supported NA +ENSG00000273983 HIST1H3G testis cells in seminiferous ducts High Supported NA +ENSG00000273983 HIST1H3G testis Leydig cells High Supported NA +ENSG00000274267 HIST1H3B epididymis glandular cells High Supported NA +ENSG00000274267 HIST1H3B prostate glandular cells High Supported NA +ENSG00000274267 HIST1H3B seminal vesicle glandular cells High Supported NA +ENSG00000274267 HIST1H3B testis cells in seminiferous ducts High Supported NA +ENSG00000274267 HIST1H3B testis Leydig cells High Supported NA +ENSG00000274274 GAGE13 testis cells in seminiferous ducts High Supported Q4V321 +ENSG00000274274 GAGE13 testis pachytene spermatocytes Low Supported Q4V321 +ENSG00000274274 GAGE13 testis preleptotene spermatocytes High Supported Q4V321 +ENSG00000274274 GAGE13 testis spermatogonia High Supported Q4V321 +ENSG00000274290 HIST1H2BE epididymis glandular cells High Supported NA +ENSG00000274290 HIST1H2BE prostate glandular cells High Supported NA +ENSG00000274290 HIST1H2BE seminal vesicle glandular cells High Supported NA +ENSG00000274290 HIST1H2BE testis cells in seminiferous ducts High Supported NA +ENSG00000274290 HIST1H2BE testis Leydig cells High Supported NA +ENSG00000274391 TPTE testis pachytene spermatocytes High Enhanced P56180 +ENSG00000274391 TPTE testis round or early spermatids High Enhanced P56180 +ENSG00000274600 RIMBP3B testis elongated or late spermatids High Supported A6NNM3 +ENSG00000274600 RIMBP3B testis Leydig cells Low Supported A6NNM3 +ENSG00000274600 RIMBP3B testis pachytene spermatocytes High Supported A6NNM3 +ENSG00000274600 RIMBP3B testis preleptotene spermatocytes Low Supported A6NNM3 +ENSG00000274600 RIMBP3B testis round or early spermatids High Supported A6NNM3 +ENSG00000274600 RIMBP3B testis spermatogonia Low Supported A6NNM3 +ENSG00000274618 HIST1H4F epididymis glandular cells Low Supported NA +ENSG00000274618 HIST1H4F prostate glandular cells Low Supported NA +ENSG00000274618 HIST1H4F seminal vesicle glandular cells Medium Supported NA +ENSG00000274618 HIST1H4F testis cells in seminiferous ducts Medium Supported NA +ENSG00000274641 HIST1H2BO epididymis glandular cells High Supported P23527 +ENSG00000274641 HIST1H2BO prostate glandular cells High Supported P23527 +ENSG00000274641 HIST1H2BO seminal vesicle glandular cells High Supported P23527 +ENSG00000274641 HIST1H2BO testis cells in seminiferous ducts High Supported P23527 +ENSG00000274641 HIST1H2BO testis Leydig cells High Supported P23527 +ENSG00000274750 HIST1H3E epididymis glandular cells High Supported NA +ENSG00000274750 HIST1H3E prostate glandular cells High Supported NA +ENSG00000274750 HIST1H3E seminal vesicle glandular cells High Supported NA +ENSG00000274750 HIST1H3E testis cells in seminiferous ducts High Supported NA +ENSG00000274750 HIST1H3E testis Leydig cells High Supported NA +ENSG00000274997 HIST1H2AH epididymis glandular cells Medium Supported Q96KK5 +ENSG00000274997 HIST1H2AH prostate glandular cells Low Supported Q96KK5 +ENSG00000274997 HIST1H2AH seminal vesicle glandular cells Medium Supported Q96KK5 +ENSG00000274997 HIST1H2AH testis cells in seminiferous ducts High Supported Q96KK5 +ENSG00000274997 HIST1H2AH testis Leydig cells Low Supported Q96KK5 +ENSG00000275126 HIST1H4L epididymis glandular cells Low Supported NA +ENSG00000275126 HIST1H4L prostate glandular cells Low Supported NA +ENSG00000275126 HIST1H4L seminal vesicle glandular cells Medium Supported NA +ENSG00000275126 HIST1H4L testis cells in seminiferous ducts Medium Supported NA +ENSG00000275183 LENG9 epididymis glandular cells Low Enhanced NA +ENSG00000275183 LENG9 seminal vesicle glandular cells Low Enhanced NA +ENSG00000275183 LENG9 testis cells in seminiferous ducts Medium Enhanced NA +ENSG00000275183 LENG9 testis Leydig cells Medium Enhanced NA +ENSG00000275221 HIST1H2AK epididymis glandular cells Medium Supported NA +ENSG00000275221 HIST1H2AK prostate glandular cells Low Supported NA +ENSG00000275221 HIST1H2AK seminal vesicle glandular cells Medium Supported NA +ENSG00000275221 HIST1H2AK testis cells in seminiferous ducts High Supported NA +ENSG00000275221 HIST1H2AK testis Leydig cells Low Supported NA +ENSG00000275379 HIST1H3I epididymis glandular cells High Supported NA +ENSG00000275379 HIST1H3I prostate glandular cells High Supported NA +ENSG00000275379 HIST1H3I seminal vesicle glandular cells High Supported NA +ENSG00000275379 HIST1H3I testis cells in seminiferous ducts High Supported NA +ENSG00000275379 HIST1H3I testis Leydig cells High Supported NA +ENSG00000275395 FCGBP seminal vesicle glandular cells Low Enhanced A0A087WXI2 +ENSG00000275410 HNF1B epididymis glandular cells Low Enhanced NA +ENSG00000275410 HNF1B testis Leydig cells Low Enhanced NA +ENSG00000275663 HIST1H4G epididymis glandular cells Low Supported Q99525 +ENSG00000275663 HIST1H4G prostate glandular cells Low Supported Q99525 +ENSG00000275663 HIST1H4G seminal vesicle glandular cells Medium Supported Q99525 +ENSG00000275663 HIST1H4G testis cells in seminiferous ducts Medium Supported Q99525 +ENSG00000275713 HIST1H2BH epididymis glandular cells High Supported Q93079 +ENSG00000275713 HIST1H2BH prostate glandular cells High Supported Q93079 +ENSG00000275713 HIST1H2BH seminal vesicle glandular cells High Supported Q93079 +ENSG00000275713 HIST1H2BH testis cells in seminiferous ducts High Supported Q93079 +ENSG00000275713 HIST1H2BH testis Leydig cells High Supported Q93079 +ENSG00000275714 HIST1H3A epididymis glandular cells High Supported NA +ENSG00000275714 HIST1H3A prostate glandular cells High Supported NA +ENSG00000275714 HIST1H3A seminal vesicle glandular cells High Supported NA +ENSG00000275714 HIST1H3A testis cells in seminiferous ducts High Supported NA +ENSG00000275714 HIST1H3A testis Leydig cells High Supported NA +ENSG00000275722 LYZL6 testis Leydig cells Low Supported NA +ENSG00000275793 RIMBP3 testis elongated or late spermatids High Supported Q9UFD9 +ENSG00000275793 RIMBP3 testis Leydig cells Low Supported Q9UFD9 +ENSG00000275793 RIMBP3 testis pachytene spermatocytes High Supported Q9UFD9 +ENSG00000275793 RIMBP3 testis preleptotene spermatocytes Low Supported Q9UFD9 +ENSG00000275793 RIMBP3 testis round or early spermatids High Supported Q9UFD9 +ENSG00000275793 RIMBP3 testis spermatogonia Low Supported Q9UFD9 +ENSG00000275835 TUBGCP5 epididymis glandular cells Medium Supported Q96RT8 +ENSG00000275835 TUBGCP5 prostate glandular cells Low Supported Q96RT8 +ENSG00000275835 TUBGCP5 seminal vesicle glandular cells Medium Supported Q96RT8 +ENSG00000275835 TUBGCP5 testis cells in seminiferous ducts Medium Supported Q96RT8 +ENSG00000275835 TUBGCP5 testis Leydig cells High Supported Q96RT8 +ENSG00000275895 U2AF1L5 epididymis glandular cells High Supported P0DN76 +ENSG00000275895 U2AF1L5 prostate glandular cells Medium Supported P0DN76 +ENSG00000275895 U2AF1L5 seminal vesicle glandular cells High Supported P0DN76 +ENSG00000275895 U2AF1L5 testis cells in seminiferous ducts High Supported P0DN76 +ENSG00000275895 U2AF1L5 testis Leydig cells High Supported P0DN76 +ENSG00000276043 UHRF1 testis cells in seminiferous ducts Medium Enhanced Q96T88 +ENSG00000276180 HIST1H4I epididymis glandular cells Low Supported NA +ENSG00000276180 HIST1H4I prostate glandular cells Low Supported NA +ENSG00000276180 HIST1H4I seminal vesicle glandular cells Medium Supported NA +ENSG00000276180 HIST1H4I testis cells in seminiferous ducts Medium Supported NA +ENSG00000276368 HIST1H2AJ epididymis glandular cells Medium Supported Q99878 +ENSG00000276368 HIST1H2AJ prostate glandular cells Low Supported Q99878 +ENSG00000276368 HIST1H2AJ seminal vesicle glandular cells Medium Supported Q99878 +ENSG00000276368 HIST1H2AJ testis cells in seminiferous ducts High Supported Q99878 +ENSG00000276368 HIST1H2AJ testis Leydig cells Low Supported Q99878 +ENSG00000276410 HIST1H2BB epididymis glandular cells High Supported P33778 +ENSG00000276410 HIST1H2BB prostate glandular cells High Supported P33778 +ENSG00000276410 HIST1H2BB seminal vesicle glandular cells High Supported P33778 +ENSG00000276410 HIST1H2BB testis cells in seminiferous ducts High Supported P33778 +ENSG00000276410 HIST1H2BB testis Leydig cells High Supported P33778 +ENSG00000276410 HIST1H2BB testis pachytene spermatocytes Medium Supported P33778 +ENSG00000276410 HIST1H2BB testis peritubular cells High Supported P33778 +ENSG00000276410 HIST1H2BB testis preleptotene spermatocytes High Supported P33778 +ENSG00000276410 HIST1H2BB testis round or early spermatids Low Supported P33778 +ENSG00000276410 HIST1H2BB testis sertoli cells Medium Supported P33778 +ENSG00000276410 HIST1H2BB testis spermatogonia High Supported P33778 +ENSG00000276903 HIST1H2AL epididymis glandular cells Medium Supported NA +ENSG00000276903 HIST1H2AL prostate glandular cells Low Supported NA +ENSG00000276903 HIST1H2AL seminal vesicle glandular cells Medium Supported NA +ENSG00000276903 HIST1H2AL testis cells in seminiferous ducts High Supported NA +ENSG00000276903 HIST1H2AL testis Leydig cells Low Supported NA +ENSG00000276966 HIST1H4E epididymis glandular cells Low Supported NA +ENSG00000276966 HIST1H4E prostate glandular cells Low Supported NA +ENSG00000276966 HIST1H4E seminal vesicle glandular cells Medium Supported NA +ENSG00000276966 HIST1H4E testis cells in seminiferous ducts Medium Supported NA +ENSG00000277075 HIST1H2AE epididymis glandular cells High Supported NA +ENSG00000277075 HIST1H2AE prostate glandular cells Medium Supported NA +ENSG00000277075 HIST1H2AE seminal vesicle glandular cells High Supported NA +ENSG00000277075 HIST1H2AE testis cells in seminiferous ducts High Supported NA +ENSG00000277075 HIST1H2AE testis Leydig cells Medium Supported NA +ENSG00000277157 HIST1H4D epididymis glandular cells Low Supported NA +ENSG00000277157 HIST1H4D prostate glandular cells Low Supported NA +ENSG00000277157 HIST1H4D seminal vesicle glandular cells Medium Supported NA +ENSG00000277157 HIST1H4D testis cells in seminiferous ducts Medium Supported NA +ENSG00000277224 HIST1H2BF epididymis glandular cells High Supported NA +ENSG00000277224 HIST1H2BF prostate glandular cells High Supported NA +ENSG00000277224 HIST1H2BF seminal vesicle glandular cells High Supported NA +ENSG00000277224 HIST1H2BF testis cells in seminiferous ducts High Supported NA +ENSG00000277224 HIST1H2BF testis Leydig cells High Supported NA +ENSG00000277363 SRCIN1 testis cells in seminiferous ducts Low Enhanced NA +ENSG00000277443 MARCKS epididymis glandular cells Medium Enhanced P29966 +ENSG00000277443 MARCKS prostate glandular cells Medium Enhanced P29966 +ENSG00000277443 MARCKS seminal vesicle glandular cells Medium Enhanced P29966 +ENSG00000277443 MARCKS testis cells in seminiferous ducts High Enhanced P29966 +ENSG00000277443 MARCKS testis Leydig cells Low Enhanced P29966 +ENSG00000277535 RP13-347D8.7 testis cells in seminiferous ducts Medium Supported A0A0U1RQG5 +ENSG00000277775 HIST1H3F epididymis glandular cells High Supported NA +ENSG00000277775 HIST1H3F prostate glandular cells High Supported NA +ENSG00000277775 HIST1H3F seminal vesicle glandular cells High Supported NA +ENSG00000277775 HIST1H3F testis cells in seminiferous ducts High Supported NA +ENSG00000277775 HIST1H3F testis Leydig cells High Supported NA +ENSG00000278023 RDM1 testis cells in seminiferous ducts Medium Enhanced NA +ENSG00000278085 CT45A8 testis pachytene spermatocytes High Supported P0DMV1 +ENSG00000278085 CT45A8 testis preleptotene spermatocytes Medium Supported P0DMV1 +ENSG00000278085 CT45A8 testis spermatogonia High Supported P0DMV1 +ENSG00000278272 HIST1H3C epididymis glandular cells High Supported NA +ENSG00000278272 HIST1H3C prostate glandular cells High Supported NA +ENSG00000278272 HIST1H3C seminal vesicle glandular cells High Supported NA +ENSG00000278272 HIST1H3C testis cells in seminiferous ducts High Supported NA +ENSG00000278272 HIST1H3C testis Leydig cells High Supported NA +ENSG00000278289 CT45A6 testis cells in seminiferous ducts High Supported P0DMU7 +ENSG00000278463 HIST1H2AB epididymis glandular cells Medium Supported NA +ENSG00000278463 HIST1H2AB prostate glandular cells Low Supported NA +ENSG00000278463 HIST1H2AB seminal vesicle glandular cells Medium Supported NA +ENSG00000278463 HIST1H2AB testis cells in seminiferous ducts High Supported NA +ENSG00000278463 HIST1H2AB testis Leydig cells Low Supported NA +ENSG00000278535 DHRS11 testis cells in seminiferous ducts Low Enhanced NA +ENSG00000278535 DHRS11 testis Leydig cells Low Enhanced NA +ENSG00000278588 HIST1H2BI epididymis glandular cells High Supported NA +ENSG00000278588 HIST1H2BI prostate glandular cells High Supported NA +ENSG00000278588 HIST1H2BI seminal vesicle glandular cells High Supported NA +ENSG00000278588 HIST1H2BI testis cells in seminiferous ducts High Supported NA +ENSG00000278588 HIST1H2BI testis Leydig cells High Supported NA +ENSG00000278619 MRM1 epididymis glandular cells Low Supported NA +ENSG00000278619 MRM1 prostate glandular cells Low Supported NA +ENSG00000278619 MRM1 seminal vesicle glandular cells Medium Supported NA +ENSG00000278619 MRM1 testis cells in seminiferous ducts Low Supported NA +ENSG00000278619 MRM1 testis Leydig cells Medium Supported NA +ENSG00000278637 HIST1H4A epididymis glandular cells Medium Supported NA +ENSG00000278637 HIST1H4A prostate glandular cells Medium Supported NA +ENSG00000278637 HIST1H4A seminal vesicle glandular cells Medium Supported NA +ENSG00000278637 HIST1H4A testis cells in seminiferous ducts High Supported NA +ENSG00000278637 HIST1H4A testis Leydig cells Medium Supported NA +ENSG00000278646 RP1-321E8.5 testis cells in seminiferous ducts Medium Supported A0A087WWU0 +ENSG00000278677 HIST1H2AM epididymis glandular cells Medium Supported NA +ENSG00000278677 HIST1H2AM prostate glandular cells Low Supported NA +ENSG00000278677 HIST1H2AM seminal vesicle glandular cells Medium Supported NA +ENSG00000278677 HIST1H2AM testis cells in seminiferous ducts High Supported NA +ENSG00000278677 HIST1H2AM testis Leydig cells Low Supported NA +ENSG00000278705 HIST1H4B epididymis glandular cells Low Supported NA +ENSG00000278705 HIST1H4B prostate glandular cells Low Supported NA +ENSG00000278705 HIST1H4B seminal vesicle glandular cells Medium Supported NA +ENSG00000278705 HIST1H4B testis cells in seminiferous ducts Medium Supported NA +ENSG00000278828 HIST1H3H epididymis glandular cells High Supported NA +ENSG00000278828 HIST1H3H prostate glandular cells High Supported NA +ENSG00000278828 HIST1H3H seminal vesicle glandular cells High Supported NA +ENSG00000278828 HIST1H3H testis cells in seminiferous ducts High Supported NA +ENSG00000278828 HIST1H3H testis Leydig cells High Supported NA +ENSG00000278845 MRPL45 epididymis glandular cells Medium Enhanced A0A087X2D5 +ENSG00000278845 MRPL45 prostate glandular cells Medium Enhanced A0A087X2D5 +ENSG00000278845 MRPL45 seminal vesicle glandular cells Medium Enhanced A0A087X2D5 +ENSG00000278845 MRPL45 testis cells in seminiferous ducts Medium Enhanced A0A087X2D5 +ENSG00000278845 MRPL45 testis Leydig cells High Enhanced A0A087X2D5 +ENSG00000280987 MATR3 epididymis glandular cells High Supported A8MXP9 +ENSG00000280987 MATR3 prostate glandular cells High Supported A8MXP9 +ENSG00000280987 MATR3 seminal vesicle glandular cells High Supported A8MXP9 +ENSG00000280987 MATR3 testis cells in seminiferous ducts High Supported A8MXP9 +ENSG00000280987 MATR3 testis Leydig cells High Supported A8MXP9 +ENSG00000283706 PRSS50 testis cells in seminiferous ducts High Supported NA +ENSG00000283706 PRSS50 testis elongated or late spermatids Medium Supported NA +ENSG00000283706 PRSS50 testis pachytene spermatocytes High Supported NA +ENSG00000283706 PRSS50 testis round or early spermatids Medium Supported NA +ENSG00000284308 C2orf81 testis Leydig cells Low Enhanced A6NN90