Fixed RE for excluding Romanze (without relying on $ as EOL)

Proved as correct

corpusStats(kco, "textType=/.*[Rr]oman.*/")
corpusStats(kco, "textType=/.*[Rr]omanz.*/")
corpusStats(kco, "textType=/.*[Rr]oman([^z].*|$)/")
corpusStats(kco, "textType=/.*[Rr]oman([^z].*)?/")

Getting size of virtual corpus "textType=/.*[Rr]oman.*/": 35793450 tokens
Getting size of virtual corpus "textType=/.*[Rr]omanz.*/": 25404 tokens
Getting size of virtual corpus "textType=/.*[Rr]oman([^z].*|$)/": 9398408 tokens
Getting size of virtual corpus "textType=/.*[Rr]oman([^z].*)?/": 35768046 tokens

35793450 - 25404 = 35768046
diff --git a/shiny/app.R b/shiny/app.R
index 3473c82..2bce6dc 100644
--- a/shiny/app.R
+++ b/shiny/app.R
@@ -167,7 +167,8 @@
     corpus <- vcFromString(input$cq)
 
     texttypes <-
-      c("/[^:]*[Zz]eitung.*/", "/(Zeitschrift|Magazin).*/", "/Agenturmeldung.*/", "/Enzyklopädie.*/", "/.*Diskussion.*/", "/.*[Rr]oman([^z].*|$)/", "/Newsgroup.*/", "/Tagebuch.*/", "/.*Sachbuch.*/")
+      c("/[^:]*[Zz]eitung.*/", "/(Zeitschrift|Magazin).*/", "/Agenturmeldung.*/", "/Enzyklopädie.*/", "/.*Diskussion.*/",
+        "/.*[Rr]oman([^z].*)?/", "/Newsgroup.*/", "/Tagebuch.*/", "/.*Sachbuch.*/")
 
     df <- expand_grid(corpus=corpus, texttype=texttypes) %>%
       mutate(vc = sprintf("%stextType=%s", corpus, texttype)) %>%
@@ -179,9 +180,9 @@
       hc_xAxis(categories = df$texttype %>%
                  str_replace_all("Zz", "Z") %>%
                  str_replace_all("Rr", "R") %>%
+                 str_replace_all("Bb", "B") %>%
                  str_replace_all("z]", "") %>%
-                 str_replace_all("\\|\\$", "") %>%
-                 str_replace_all("[/.*)():^\\[\\]]", "") %>%
+                 str_replace_all("[/.*)():^\\[\\]\\?]", "") %>%
                  str_replace_all("\\|", "/")) %>%
       hc_title(text="Texttyp")
     hc