{-# LANGUAGE LambdaCase       #-}
{-# LANGUAGE TupleSections    #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns     #-}

{-# OPTIONS_HADDOCK prune #-}
{-# OPTIONS_GHC -fno-warn-missing-export-lists #-}

-- |
-- Module    : Aura.Languages
-- Copyright : (c) Colin Woodbury, 2012 - 2021
-- License   : GPL3
-- Maintainer: Colin Woodbury <colin@fosskers.ca>
--
-- All output strings that a user can be shown.
-- All normal restrictions on line length do not apply for this file, and this file only.

module Aura.Languages where

import           Aura.Colour
import qualified Aura.Languages.Fields as Fields
import           Aura.Types
import           Data.Ratio ((%))
import           Prettyprinter
import           Prettyprinter.Render.Terminal
import           RIO
import qualified RIO.List as L
import qualified RIO.Map as M
import qualified RIO.Text as T

---

-- | Thank you all!
translators :: Map Language Text
translators :: Map Language Text
translators = [(Language, Text)] -> Map Language Text
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
    [ (Language
Polish,     Text
"Chris Warrick / Michał Kurek")
    , (Language
Croatian,   Text
"Denis Kasak / \"stranac\"")
    , (Language
Swedish,    Text
"Fredrik Haikarainen / Daniel Beecham")
    , (Language
German,     Text
"Lukas Niederbremer / Jonas Platte")
    , (Language
Spanish,    Text
"Alejandro Gómez / Sergio Conde / Max Ferrer")
    , (Language
Portuguese, Text
"Henry Kupty / Thiago Perrotta / Wagner Amaral")
    , (Language
French,     Text
"Ma Jiehong / Fabien Dubosson")
    , (Language
Russian,    Text
"Kyrylo Silin / Alexey Kotlyarov")
    , (Language
Italian,    Text
"Bob Valantin / Cristian Tentella")
    , (Language
Serbian,    Text
"Filip Brcic")
    , (Language
Norwegian,  Text
"\"chinatsun\"")
    , (Language
Indonesia,  Text
"\"pak tua Greg\"")
    , (Language
Chinese,    Text
"Kai Zhang")
    , (Language
Japanese,   Text
"Onoue Takuro / Colin Woodbury")
    , (Language
Esperanto,  Text
"Zachary Matthews")
    , (Language
Dutch,      Text
"Joris Blanken / Heimen Stoffels")
    , (Language
Turkish,    Text
"Cihan Alkan")
    , (Language
Arabic,     Text
"\"Array in a Matrix\"")
    , (Language
Ukrainian,  Text
"Andriy Cherniy")
    , (Language
Romanian,   Text
"90 / benone")
    , (Language
Vietnamese, Text
"\"Kritiqual\"")
    , (Language
Czech,      Text
"Daniel Rosel")
    , (Language
Korean,     Text
"\"Nioden\"")
    ]

translatorMsgTitle :: Language -> Text
translatorMsgTitle :: Language -> Text
translatorMsgTitle = \case
    Language
Japanese   -> Text
"Auraの翻訳者:"
    Language
Polish     -> Text
"Tłumacze Aury:"
    Language
Arabic     -> Text
"Aura مترجم"
    Language
Turkish    -> Text
"Aura Çevirmeni:"
    Language
Croatian   -> Text
"Aura Prevoditelji:"
    Language
Swedish    -> Text
"Aura Översättare:"
    Language
German     -> Text
"Aura Übersetzer:"
    Language
Spanish    -> Text
"Traductores de Aura:"
    Language
Portuguese -> Text
"Tradutores de Aura:"
    Language
French     -> Text
"Traducteurs d'Aura:"
    Language
Russian    -> Text
"Переводчики Aura:"
    Language
Italian    -> Text
"Traduttori di Aura:"
    Language
Serbian    -> Text
"Преводиоци Аура:"
    Language
Norwegian  -> Text
"Aura Oversettere:"
    Language
Indonesia  -> Text
"Penerjemah Aura:"
    Language
Chinese    -> Text
"Aura 的翻译者:"
    Language
Esperanto  -> Text
"Tradukistoj de Aura:"
    Language
Dutch      -> Text
"Aura-vertalers:"
    Language
Ukrainian  -> Text
"Перекладачі Aura:"
    Language
Romanian   -> Text
"Traducători Aura:"
    Language
Vietnamese -> Text
"Dịch giả của Aura:"
    Language
Czech      -> Text
"Překladači Aury:"
    Language
Korean     -> Text
"Aura 번역자:"
    Language
_          -> Text
"Aura Translators:"

translatorMsg :: Language -> [Text]
translatorMsg :: Language -> [Text]
translatorMsg Language
lang = Text
title Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
names
  where
    title :: Text
    title :: Text
title = Language -> Text
translatorMsgTitle Language
lang

    names :: [Text]
    names :: [Text]
names = (Language -> Maybe Text) -> [Language] -> [Text]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (\Language
l -> (Text, Language) -> Text
formatLang ((Text, Language) -> Text)
-> (Text -> (Text, Language)) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (,Language
l) (Text -> Text) -> Maybe Text -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Language -> Map Language Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Language
l Map Language Text
translators) [Language
English ..]

    formatLang :: (Text, Language) -> Text
    formatLang :: (Text, Language) -> Text
formatLang (Text
translator, Language
lang') = Text
" (" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Language -> String
forall a. Show a => a -> String
show Language
lang') Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
") " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
translator

-- | Make some `Text` cyan. Previous wrapped things in backticks.
bt :: Pretty a => a -> Doc AnsiStyle
bt :: a -> Doc AnsiStyle
bt = Doc AnsiStyle -> Doc AnsiStyle
cyan (Doc AnsiStyle -> Doc AnsiStyle)
-> (a -> Doc AnsiStyle) -> a -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty

whitespace :: Language -> Char
whitespace :: Language -> Char
whitespace Language
Japanese = Char
' '  -- \12288
whitespace Language
_        = Char
' '   -- \32

langFromLocale :: Text -> Maybe Language
langFromLocale :: Text -> Maybe Language
langFromLocale = Int -> Text -> Text
T.take Int
2 (Text -> Text)
-> (Text -> Maybe Language) -> Text -> Maybe Language
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> \case
  Text
"ja" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Japanese
  Text
"ar" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Arabic
  Text
"tr" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Turkish
  Text
"pl" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Polish
  Text
"hr" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Croatian
  Text
"sv" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Swedish
  Text
"de" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
German
  Text
"es" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Spanish
  Text
"pt" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Portuguese
  Text
"fr" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
French
  Text
"ru" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Russian
  Text
"it" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Italian
  Text
"sr" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Serbian
  Text
"nb" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Norwegian
  Text
"id" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Indonesia
  Text
"zh" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Chinese
  Text
"eo" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Esperanto
  Text
"nl" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Dutch
  Text
"en" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
English
  Text
"uk" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Ukrainian
  Text
"ro" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Romanian
  Text
"vi" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Vietnamese
  Text
"cs" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Czech
  Text
"ko" -> Language -> Maybe Language
forall a. a -> Maybe a
Just Language
Korean
  Text
_    -> Maybe Language
forall a. Maybe a
Nothing

----------------------
-- Aura/Core functions
----------------------
-- NEEDS TRANSLATION
checkDBLock_1 :: Language -> Doc AnsiStyle
checkDBLock_1 :: Language -> Doc AnsiStyle
checkDBLock_1 = \case
    Language
Japanese   -> Doc AnsiStyle
"パッケージデータベースが閉鎖されている状態です。開放したらキーを押して続行してください。"
    Language
Polish     -> Doc AnsiStyle
"Baza pakietów jest zablokowana. Kiedy zostanie odblokowana naciśnij enter aby kontynuować"
    Language
Arabic     -> Doc AnsiStyle
".قاعدة البيانات مقفلة. اضغط ادخال عندما تفتح قاعدة البيانات للاستمرار"
    Language
Turkish    -> Doc AnsiStyle
"Paket veritabanı kilitlendi. Devam etmek için kilidi açıldığında enter tuşuna basın."
    Language
Croatian   -> Doc AnsiStyle
"Baza paketa je zaključana. Kad se otključa, pritisnite enter da biste nastavili."
    Language
German     -> Doc AnsiStyle
"Die Paketdatenbank ist gesperrt. Drücken Sie Enter wenn sie entsperrt ist um fortzufahren."
    Language
Spanish    -> Doc AnsiStyle
"La base de datos de paquetes está bloqueada. Presiona enter cuando esté desbloqueada para continuar."
    Language
Norwegian  -> Doc AnsiStyle
"Pakkedatabasen er låst. Trykk enter når den er åpnet for å fortsette."
    Language
French     -> Doc AnsiStyle
"La base de données des paquets est bloquée. Appuyez sur enter pour continuer."
    Language
Portuguese -> Doc AnsiStyle
"Banco de dados de pacote travado. Aperte 'enter' quando estiver destravado para poder continuar."
    Language
Russian    -> Doc AnsiStyle
"База данных пакетов заблокирована. Нажмите \"Ввод\", когда она разблокируется, чтобы продолжить."
    Language
Italian    -> Doc AnsiStyle
"Non è stato possibile accedere alla banca dati dei pacchetti. Per continuare premere invio quando sarà di nuovo disponibile."
    Language
Chinese    -> Doc AnsiStyle
"包数据库已锁定。请在解锁后按下回车以继续。"
    Language
Swedish    -> Doc AnsiStyle
"Paketdatabasen är låst. Klicka på enter när den är upplåst."
    Language
Esperanto  -> Doc AnsiStyle
"La datumbazo de pakaĵoj estas ŝlosita. Premu enen-klavo kiam la datumbazo estas malŝlosita por daŭrigi"
    Language
Dutch      -> Doc AnsiStyle
"De pakketdatabank is vergrendeld. Druk op enter zodra de databank ontgrendeld is."
    Language
Ukrainian  -> Doc AnsiStyle
"База даних пакетів заблокована. Натисніть Enter, коли вона розблокується, щоб продовжити."
    Language
Romanian   -> Doc AnsiStyle
"Baza de date de pachete este blocată. Apăsați Enter după ce s-a deblocat pentru a continua."
    Language
Vietnamese -> Doc AnsiStyle
"Cơ sở dữ liệu của gói đã bị khóa. Nhấn Enter sau khi nó được mở khóa để tiếp tục."
    Language
Czech      -> Doc AnsiStyle
"Databáze balíčků je uzamčena. Až bude odemčena, stiskněte Enter pro pokračování."
    Language
Korean     -> Doc AnsiStyle
"패키지 데이터베이스가 잠겨있습니다. 계속하려면 Enter 키를 누르시오."
    Language
_          -> Doc AnsiStyle
"The package database is locked. Press enter when it's unlocked to continue."

trueRoot_3 :: Language -> Doc AnsiStyle
trueRoot_3 :: Language -> Doc AnsiStyle
trueRoot_3 = \case
    Language
Japanese   -> Doc AnsiStyle
"「root」としてパッケージを作成するのは「makepkg v4.2」で不可能になりました。"
    Language
Arabic     -> Doc AnsiStyle
".makepkg v4.2 البناء كمشرف لم يعد ممكنا في"
    Language
Polish     -> Doc AnsiStyle
"Od makepkg v4.2, budowanie jako root nie jest dozwolone."
    Language
Turkish    -> Doc AnsiStyle
"Makepkg v4.2'den itibaren, kök olarak oluşturmak artık mümkün değildir."
    Language
German     -> Doc AnsiStyle
"Seit makepkg v4.2 ist es nicht mehr möglich als root zu bauen."
    Language
Spanish    -> Doc AnsiStyle
"Desde makepkg v4.2 no es posible compilar paquetes como root."
    Language
Portuguese -> Doc AnsiStyle
"A partir da versão v4.2 de makepkg, não é mais possível compilar como root."
    Language
Russian    -> Doc AnsiStyle
"С версии makepkg v4.2 сборка от имени root более невозможна."
    Language
Italian    -> Doc AnsiStyle
"A partire dalla versione 4.2 di makepkg non è più possibile compilare come root."
    Language
Chinese    -> Doc AnsiStyle
"自从 makepkg v4.2 以后,就不能以根用户身份构建软件了。"
    Language
Swedish    -> Doc AnsiStyle
"I makepkg v4.2 och uppåt är det inte tillåtet att bygga som root."
    Language
Esperanto  -> Doc AnsiStyle
"Depost makepkg v4.2, konstruanto ĉefuzante ne eblas."
    Language
Dutch      -> Doc AnsiStyle
"Sinds makepkg v4.2 is het niet meer mogelijk om als root te bouwen."
    Language
Ukrainian  -> Doc AnsiStyle
"З версії makepkg v4.2 збірка від імені root неможлива."
    Language
Romanian   -> Doc AnsiStyle
"De la versiunea makepkg v4.2 încolo, compilarea ca root nu mai este posibilă."
    Language
Vietnamese -> Doc AnsiStyle
"Kể từ makepkg v4.2, build bằng quyền root không còn khả dụng."
    Language
Czech      -> Doc AnsiStyle
"Od makepkg v4.2 již není sestavení jako root možné."
    Language
Korean     -> Doc AnsiStyle
"makepkg v4.2부터는 루트 권한으로 빌드 할 수 없습니다."
    Language
_          -> Doc AnsiStyle
"As of makepkg v4.2, building as root is no longer possible."

mustBeRoot_1 :: Language -> Doc AnsiStyle
mustBeRoot_1 :: Language -> Doc AnsiStyle
mustBeRoot_1 = let sudo :: Doc AnsiStyle
sudo = Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt @Text Text
"sudo" in \case
    Language
Japanese   -> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"を使わないとそれができない!"
    Language
Arabic     -> Doc AnsiStyle
"." Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" ﻻ يمكن اجراء هذه العملية بدون استخدام"
    Language
Polish     -> Doc AnsiStyle
"Musisz użyć " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", żeby to zrobić."
    Language
Turkish    -> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"kullanmadan bu işlemi gerçekleştiremezsiniz."
    Language
Croatian   -> Doc AnsiStyle
"Morate koristiti" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"za ovu radnju."
    Language
Swedish    -> Doc AnsiStyle
"Du måste använda " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" för det."
    Language
German     -> Doc AnsiStyle
"Sie müssen dafür " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" benutzen."
    Language
Spanish    -> Doc AnsiStyle
"Tienes que utilizar " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" para eso."
    Language
Portuguese -> Doc AnsiStyle
"Utilize " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" para isso."
    Language
French     -> Doc AnsiStyle
"Vous devez utiliser " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" pour ça."
    Language
Russian    -> Doc AnsiStyle
"Необходимо использовать " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" для этого."
    Language
Italian    -> Doc AnsiStyle
"Per eseguire questa operazione è necessario utilizzare " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Serbian    -> Doc AnsiStyle
"Морате да користите " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" за ову радњу."
    Language
Norwegian  -> Doc AnsiStyle
"Du må bruke " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" for det."
    Language
Indonesia  -> Doc AnsiStyle
"Anda harus menggunakan " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" untuk melakukannya."
    Language
Chinese    -> Doc AnsiStyle
"除非是根用户,否则不能执行此操作。"
    Language
Esperanto  -> Doc AnsiStyle
"Vi ne povas fari ĉi tiun operacion, sen " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Dutch      -> Doc AnsiStyle
"U kunt deze actie niet uitvoeren zonder " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" te gebruiken."
    Language
Ukrainian  -> Doc AnsiStyle
"Для цієї дії, потрібно використати " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Romanian   -> Doc AnsiStyle
"Nu se poate folosi această operație asta fără " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Vietnamese -> Doc AnsiStyle
"Bạn không thể thực hiện hành động này nếu không dùng " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
sudo Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Czech      -> Doc AnsiStyle
"Tuto operaci nelze provést bez použití sudo."
    Language
Korean     -> Doc AnsiStyle
"루트 권한으로 실행해야 합니다."
    Language
_          -> Doc AnsiStyle
"You cannot perform this operation without using sudo."

-----------------------
-- Aura/Build functions
-----------------------
buildPackages_1 :: PkgName -> Language -> Doc AnsiStyle
buildPackages_1 :: PkgName -> Language -> Doc AnsiStyle
buildPackages_1 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle)
-> (PkgName -> Text) -> PkgName -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PkgName -> Text
pnName -> Doc AnsiStyle
p) = \case
    Language
Japanese   -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"を作成中・・・"
    Language
Arabic     -> Doc AnsiStyle
"..." Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" بناء"
    Language
Turkish    -> Doc AnsiStyle
"İnşa ediliyor " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."
    Language
Polish     -> Doc AnsiStyle
"Budowanie " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."
    Language
Croatian   -> Doc AnsiStyle
"Gradim " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."
    Language
Swedish    -> Doc AnsiStyle
"Bygger paket " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."
    Language
German     -> Doc AnsiStyle
"Baue Paket " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."
    Language
Spanish    -> Doc AnsiStyle
"Compilando " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."
    Language
Portuguese -> Doc AnsiStyle
"Compilando " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."
    Language
French     -> Doc AnsiStyle
"Compilation de " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."
    Language
Russian    -> Doc AnsiStyle
"Сборка " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."
    Language
Italian    -> Doc AnsiStyle
"Compilazione di " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."
    Language
Serbian    -> Doc AnsiStyle
"Градим " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."
    Language
Norwegian  -> Doc AnsiStyle
"Bygger " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."
    Language
Indonesia  -> Doc AnsiStyle
"Membangun " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."
    Language
Chinese    -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" 正在构建中..."
    Language
Esperanto  -> Doc AnsiStyle
"Muntanta " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."
    Language
Dutch      -> Doc AnsiStyle
"Bezig met bouwen van " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"…"
    Language
Ukrainian  -> Doc AnsiStyle
"Збираємо " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."
    Language
Romanian   -> Doc AnsiStyle
"Se compilează " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."
    Language
Vietnamese -> Doc AnsiStyle
"Đang build " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."
    Language
Czech      -> Doc AnsiStyle
"Kompilace " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."
    Language
Korean     -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"빌드 중..."
    Language
_          -> Doc AnsiStyle
"Building " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"..."

buildPackages_2 :: Language -> Doc AnsiStyle
buildPackages_2 :: Language -> Doc AnsiStyle
buildPackages_2 = \case
    Language
Arabic     -> Doc AnsiStyle
".لن يتم بناء اي رزمة .'--allsource' كشف"
    Language
Polish     -> Doc AnsiStyle
"'--allsource' wykryte. Nie zostaną zbudowane żadne pakiety."
    Language
Turkish    -> Doc AnsiStyle
"'--allsource' bulundu. Yüklenebilir gerçek paketler oluşturulmayacaktır."
    Language
Spanish    -> Doc AnsiStyle
"'--allsource' detectado. No se construirán paquetes instalables reales."
    Language
Romanian   -> Doc AnsiStyle
"'--allsource' detectat. Nu se va compila oricare pachet instalabil."
    Language
Vietnamese -> Doc AnsiStyle
"'--allsource' được sử dụng. Không có gói nào sẽ được build."
    Language
Czech      -> Doc AnsiStyle
"Bylo nalezeno '-allsource'. Žádné skutečné instalovatelné balíčky nebudou sestaveny."
    Language
Korean     -> Doc AnsiStyle
"'--allsource' 감지되었습니다. 실제 설치 가능한 패키지는 빌드되지 않습니다."
    Language
Dutch      -> Doc AnsiStyle
"--allsource gedetecteerd. Er worden geen installeerbare pakketten gebouwd."
    Language
_          -> Doc AnsiStyle
"'--allsource' detected. No actual installable packages will be built."

buildPackages_3 :: FilePath -> Language -> Doc AnsiStyle
buildPackages_3 :: String -> Language -> Doc AnsiStyle
buildPackages_3 String
fp = \case
    Language
Arabic     -> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
":تم بناؤها ونسخها إلى .src.tar.gz كل ملفات"
    Language
Polish     -> Doc AnsiStyle
"Wszystkie pliki .src.tar.gz zostały zbudowane i przekopiowane do: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp
    Language
Turkish    -> Doc AnsiStyle
"Tüm .src.tar.gz dosyaları oluşturuldu ve şuraya kopyalandı: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp
    Language
Spanish    -> Doc AnsiStyle
"Todos los archivos .src.tar.gz fueron construidos y copiados a: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp
    Language
Ukrainian  -> Doc AnsiStyle
"Всі архіви .src.tar.gz були зібрані та скопійовані до: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp
    Language
Romanian   -> Doc AnsiStyle
"Toate fișierele .src.tar.gz au fost construite și copiate către: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp
    Language
Vietnamese -> Doc AnsiStyle
"Tất cả các tệp .src.tar.gz đã được build và sao chép tới: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp
    Language
Czech      -> Doc AnsiStyle
"Všechny soubory .src.tar.gz byly vytvořeny a zkopírovány do: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp
    Language
Dutch      -> Doc AnsiStyle
"Alle .src.tar.gz-bestanden zijn gebouwd en gekopieerd naar " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp
    Language
Korean     -> Doc AnsiStyle
"모든 .src.tar.gz 파일은 빌드되고 복사됩니다:" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp
    Language
_          -> Doc AnsiStyle
"All .src.tar.gz files were built and copied to: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp

buildPackages_4 :: Language -> Doc AnsiStyle
buildPackages_4 :: Language -> Doc AnsiStyle
buildPackages_4 = \case
    Language
Romanian -> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt @Text Text
"--hotedit" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"detectat, dar acestea au date în cache și vor fi omise din editare:"
    Language
Vietnamese -> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt @Text Text
"--hotedit" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"được sử dụng, những gói sau có trong cache và sẽ được bỏ qua để chỉnh sửa:"
    Language
Czech    -> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt @Text Text
"--hotedit" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"zjištěno, ale následující položky mají položky mezipaměti a budou přeskočeny pro úpravy:"
    Language
Korean   -> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt @Text Text
"--hotedit" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"감지되었지만 캐시 목록이 있으므로 편집을 위해 건너뜁니다."
    Language
Dutch      -> Doc AnsiStyle
"--hotedit gedetecteerd. De volgende pakketten zijn gecachet en zullen niet worden bewerkt:"
    Language
_        -> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt @Text Text
"--hotedit" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"detected, but the following have cache entries and will be skipped for editing:"

buildPackages_5 :: Language -> Doc AnsiStyle
buildPackages_5 :: Language -> Doc AnsiStyle
buildPackages_5 = \case
    Language
Romanian -> Doc AnsiStyle
"Se poate folosi" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt @Text Text
"--force" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"pentru a trece peste acest comportament."
    Language
Vietnamese -> Doc AnsiStyle
"Bạn có thể dùng" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt @Text Text
"--force" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"để ghi đè hành động này."
    Language
Czech    -> Doc AnsiStyle
"Můžete použít" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt @Text Text
"--force" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"k potlačení tohoto chování."
    Language
Korean   -> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt @Text Text
"--force" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"를 사용하여 이 동작을 무시할 수 있습니다."
    Language
Dutch      -> Doc AnsiStyle
"U kunt" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt @Text Text
"--force" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"toekennen om dit gedrag te omzeilen."
    Language
_        -> Doc AnsiStyle
"You can use" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt @Text Text
"--force" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"to override this behaviour."

buildFail_5 :: Language -> Doc AnsiStyle
buildFail_5 :: Language -> Doc AnsiStyle
buildFail_5 = \case
    Language
Japanese   -> Doc AnsiStyle
"パッケージ作成に失敗しました。"
    Language
Arabic     -> Doc AnsiStyle
".لقد فشل البناء"
    Language
Polish     -> Doc AnsiStyle
"Budowanie nie powiodło się."
    Language
Croatian   -> Doc AnsiStyle
"Izgradnja nije uspjela."
    Language
Swedish    -> Doc AnsiStyle
"Gick inte att bygga paket."
    Language
German     -> Doc AnsiStyle
"Bauen fehlgeschlagen."
    Language
Spanish    -> Doc AnsiStyle
"La compilación falló."
    Language
Portuguese -> Doc AnsiStyle
"Falha na compilação."
    Language
French     -> Doc AnsiStyle
"Compilation échouée."
    Language
Russian    -> Doc AnsiStyle
"Сборка не удалась."
    Language
Italian    -> Doc AnsiStyle
"Compilazione fallita."
    Language
Serbian    -> Doc AnsiStyle
"Изградња пакета није успела."
    Language
Norwegian  -> Doc AnsiStyle
"Bygging feilet."
    Language
Indonesia  -> Doc AnsiStyle
"Proses gagal."
    Language
Chinese    -> Doc AnsiStyle
"构建失败。"
    Language
Esperanto  -> Doc AnsiStyle
"Muntado paneis"
    Language
Dutch      -> Doc AnsiStyle
"Het bouwen is mislukt."
    Language
Ukrainian  -> Doc AnsiStyle
"Збірка не вдалась."
    Language
Romanian   -> Doc AnsiStyle
"Compilare nereușită."
    Language
Vietnamese -> Doc AnsiStyle
"Build thất bại."
    Language
Czech      -> Doc AnsiStyle
"Budování se nezdařilo."
    Language
Korean     -> Doc AnsiStyle
"빌드 실패"
    Language
_          -> Doc AnsiStyle
"Building failed."

-- NEEDS TRANSLATION
buildFail_6 :: Language -> Doc AnsiStyle
buildFail_6 :: Language -> Doc AnsiStyle
buildFail_6 = \case
    Language
Japanese   -> Doc AnsiStyle
"それでも続行しますか?"
    Language
Arabic     -> Doc AnsiStyle
"هل ترغب في الاستمرار على أي حال؟"
    Language
Polish     -> Doc AnsiStyle
"Czy mimo to chcesz kontynuować?"
    Language
Croatian   -> Doc AnsiStyle
"Želite li svejedno nastaviti?"
    Language
German     -> Doc AnsiStyle
"Möchten Sie trotzdem fortfahren?"
    Language
Spanish    -> Doc AnsiStyle
"¿Deseas continuar de todas formas?"
    Language
Norwegian  -> Doc AnsiStyle
"Vil du fortsette likevel?"
    Language
Italian    -> Doc AnsiStyle
"Procedere comunque?"
    Language
Portuguese -> Doc AnsiStyle
"Gostaria de continuar mesmo assim?"
    Language
French     -> Doc AnsiStyle
"Voulez-vous tout de même continuer ?"
    Language
Russian    -> Doc AnsiStyle
"Продолжить, несмотря ни на что?"
    Language
Indonesia  -> Doc AnsiStyle
"Apakah anda tetap ingin melanjutkan?"
    Language
Chinese    -> Doc AnsiStyle
"你仍然希望继续吗?"
    Language
Swedish    -> Doc AnsiStyle
"Vill du fortsätta ändå?"
    Language
Esperanto  -> Doc AnsiStyle
"Ĉu vi volas daŭrigi?"
    Language
Dutch      -> Doc AnsiStyle
"Wilt u toch doorgaan?"
    Language
Ukrainian  -> Doc AnsiStyle
"Ви все одно бажаєте продовжити?"
    Language
Romanian   -> Doc AnsiStyle
"Doriți oricum să continuați?"
    Language
Vietnamese -> Doc AnsiStyle
"Bạn có muốn tiếp tục không?"
    Language
Czech      -> Doc AnsiStyle
"Chcete přesto pokračovat?"
    Language
Korean     -> Doc AnsiStyle
"계속하시겠습니까?"
    Language
_          -> Doc AnsiStyle
"Would you like to continue anyway?"

-- NEEDS TRANSLATION
buildFail_7 :: PkgName -> Language -> Doc AnsiStyle
buildFail_7 :: PkgName -> Language -> Doc AnsiStyle
buildFail_7 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle)
-> (PkgName -> Text) -> PkgName -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PkgName -> Text
pnName -> Doc AnsiStyle
p) = \case
    Language
Japanese   -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"のビルドスクリプトを収得できませんでした。"
    Language
Arabic     -> Doc AnsiStyle
"." Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" فشل في الحصول على نصوص البناء لأجل"
    Language
Polish     -> Doc AnsiStyle
"Nie udało się pozyskać skryptów budowania dla " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
German     -> Doc AnsiStyle
"Herunterladen der Build-Skripte für " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" fehlgeschlagen."
    Language
Spanish    -> Doc AnsiStyle
"No se han podido obtener los scripts de compilación de " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Portuguese -> Doc AnsiStyle
"Falha ao obter scripts de compilação para " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Indonesia  -> Doc AnsiStyle
"Gagal mendapatkan skrip untuk " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Russian    -> Doc AnsiStyle
"Не удалось получить сценарии сборки для " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Italian    -> Doc AnsiStyle
"Non è stato possibile ottenere gli script di compilazione per " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Chinese    -> Doc AnsiStyle
"无法获得 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" 的构建脚本。"
    Language
Swedish    -> Doc AnsiStyle
"Kunde inte hämta byggskript för " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Esperanto  -> Doc AnsiStyle
"Paneis akiri muntaj skriptoj de " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Dutch      -> Doc AnsiStyle
"De bouwscripts van " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" kunnen niet worden opgehaald."
    Language
Ukrainian  -> Doc AnsiStyle
"Не вдалось отримати сценарії збірки для " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Romanian   -> Doc AnsiStyle
"Nu s-au putut obține scripturi de compilare pentru " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Vietnamese -> Doc AnsiStyle
"Không thể lấy tập lệnh build cho " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Czech      -> Doc AnsiStyle
"Nepodařilo se získat sestavení skriptů pro " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Korean     -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"의 빌드 스크립트를 가져올 수 없습니다."
    Language
_          -> Doc AnsiStyle
"Failed to obtain build scripts for " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."

buildFail_8 :: Language -> Doc AnsiStyle
buildFail_8 :: Language -> Doc AnsiStyle
buildFail_8 = \case
    Language
Japanese   -> Doc AnsiStyle
"makepkgは失敗しました。"
    Language
Arabic     -> Doc AnsiStyle
".makepkgهناك فشل في اﻟ"
    Language
Polish     -> Doc AnsiStyle
"Wystąpił problem z makepkg."
    Language
Spanish    -> Doc AnsiStyle
"Ocurrió un error al ejecutar makepkg"
    Language
Portuguese -> Doc AnsiStyle
"Ocorreu um erro ao executar makepkg"
    Language
Russian    -> Doc AnsiStyle
"Произошла ошибка makepkg."
    Language
Italian    -> Doc AnsiStyle
"C'è stato un errore nell'esecuzione di makepkg."
    Language
Esperanto  -> Doc AnsiStyle
"Paneo de makepkg okazis."
    Language
Dutch      -> Doc AnsiStyle
"Er is een fout opgetreden in makepkg."
    Language
Ukrainian  -> Doc AnsiStyle
"Сталась помилка makepkg."
    Language
Romanian   -> Doc AnsiStyle
"A fost o problemă cu makepkg."
    Language
Vietnamese -> Doc AnsiStyle
"Có lỗi khi makepkg."
    Language
Czech      -> Doc AnsiStyle
"Došlo k chybě makepkg."
    Language
Korean     -> Doc AnsiStyle
"makepkg를 실패했습니다."
    Language
_          -> Doc AnsiStyle
"There was a makepkg failure."

buildFail_9 :: Language -> Doc AnsiStyle
buildFail_9 :: Language -> Doc AnsiStyle
buildFail_9 = \case
  Language
Polish    -> Doc AnsiStyle
"Nie udało się zlokalizować żadnych zbudowanych pakietów (*.pkg.tar.xz)."
  Language
Arabic    -> Doc AnsiStyle
".(*.pkg.tar.xz) فشل في اكتشاف اي ملف من ملفات البناء"
  Language
Spanish   -> Doc AnsiStyle
"Error al detectar todos los archivo de paquete (*.pkg.tar.xz)."
  Language
Italian   -> Doc AnsiStyle
"Non è stato possibile trovare nessun archivio risultante dalla compilazione del pacchetto (*.pkg.tar.xz)."
  Language
Esperanto -> Doc AnsiStyle
"Paneis detekti ĉiujn dosierojn de pakaĵoj (*.pkg.tar.xz)."
  Language
Dutch     -> Doc AnsiStyle
"Er zijn geen gebouwde pakketbestanden aangetroffen (*.pkg.tar.xz)."
  Language
Ukrainian -> Doc AnsiStyle
"Не вдалось знайти жодного файлу пакунку (*.pkg.tar.xz)."
  Language
Romanian  -> Doc AnsiStyle
"Nu s-a detectat nici un pachet construit (*.pkg.tar.xz)."
  Language
Vietnamese -> Doc AnsiStyle
"Không thể phát hiện các tệp đã được build (*.pkg.tar.xz)."
  Language
Czech     -> Doc AnsiStyle
"Nepodařilo se detekovat žádné soubory zabudovaného balíčku (*.pkg.tar.xz)."
  Language
Korean    -> Doc AnsiStyle
"빌드된 패키지 파일 (*.pkg.tar.xz)을 검색하지 못했습니다."
  Language
_         -> Doc AnsiStyle
"Failed to detect any built package files (*.pkg.tar.xz)."

buildFail_10 :: Language -> Doc AnsiStyle
buildFail_10 :: Language -> Doc AnsiStyle
buildFail_10 = \case
  Language
Polish     -> Doc AnsiStyle
"Nie udało się zbudować żadnego pakietu."
  Language
Arabic     -> Doc AnsiStyle
".فشل بناء كل الرزم"
  Language
Spanish    -> Doc AnsiStyle
"Los paquetes no se pudieron construir."
  Language
Italian    -> Doc AnsiStyle
"Non è stato possibile compilare i pacchetti."
  Language
Esperanto  -> Doc AnsiStyle
"Ĉiuj pakaĵoj paneis munti."
  Language
Dutch      -> Doc AnsiStyle
"Het bouwen van alle pakketten is mislukt."
  Language
Ukrainian  -> Doc AnsiStyle
"Жоден пакунок не вдалося зібрати."
  Language
Romanian   -> Doc AnsiStyle
"Nu s-a putut compila nici un pachet."
  Language
Vietnamese -> Doc AnsiStyle
"Tất cả các gói build thất bại."
  Language
Czech      -> Doc AnsiStyle
"Sestavení každého balíčku se nezdařilo."
  Language
Korean     -> Doc AnsiStyle
"모든 패키지를 빌드하지 못했습니다."
  Language
_          -> Doc AnsiStyle
"Every package failed to build."

buildFail_11 :: Language -> Doc AnsiStyle
buildFail_11 :: Language -> Doc AnsiStyle
buildFail_11 = \case
  Language
Japanese   -> Doc AnsiStyle
"作成は失敗しました。エラーを見ますか?"
  Language
Arabic     -> Doc AnsiStyle
"فشل البناء. هل ترغب في رؤية الخطأ؟"
  Language
Polish     -> Doc AnsiStyle
"Budowa zakończona niepowodzeniem. Czy chcesz zobaczyć błąd?"
  Language
Spanish    -> Doc AnsiStyle
"Construcción fallida. ¿Te gustaría ver el error?"
  Language
Italian    -> Doc AnsiStyle
"La compilazione è fallita. Visionare l'errore?"
  Language
Esperanto  -> Doc AnsiStyle
"Muntado paneis. Ĉu vi volas vidi la eraron?"
  Language
Dutch      -> Doc AnsiStyle
"Het bouwen is mislukt. Wilt u de foutmeldingen bekijken?"
  Language
Ukrainian  -> Doc AnsiStyle
"Збірка не вдалась. Бажаєте побачити помилку?"
  Language
Romanian   -> Doc AnsiStyle
"Compilare nereușită. Doriți să vedeți eroarea?"
  Language
Vietnamese -> Doc AnsiStyle
"Build thất bại. Bạn có muốn xem lịch sử lỗi?"
  Language
Czech      -> Doc AnsiStyle
"Budování se nezdařilo. Chcete vidět chybu?"
  Language
Korean     -> Doc AnsiStyle
"빌드를 실패했습니다. 오류를 확인하시겠습니까?"
  Language
_          -> Doc AnsiStyle
"Building failed. Would you like to see the error?"

buildFail_12 :: Language -> Doc AnsiStyle
buildFail_12 :: Language -> Doc AnsiStyle
buildFail_12 = \case
    Language
Polish     -> Doc AnsiStyle
"Błąd podczas pobierania najnowszych aktualizacji poprzez 'git pull'."
    Language
Arabic     -> Doc AnsiStyle
".على اخر تحديث 'git pull' فشل حصول"
    Language
Spanish    -> Doc AnsiStyle
"Error al 'git pull' las últimas actualizaciones."
    Language
Ukrainian  -> Doc AnsiStyle
"Не вдалося використати 'git pull' для отримання останніх оновлень."
    Language
Romanian   -> Doc AnsiStyle
"Nu a reușit 'git pull' să descarce cele mai recente actualizări."
    Language
Vietnamese -> Doc AnsiStyle
"Thất bại trong việc 'git pull' để cập nhật."
    Language
Czech      -> Doc AnsiStyle
"Nepodařilo se 'git stáhnout' nejnovější aktualizace."
    Language
Korean     -> Doc AnsiStyle
"최신 버전 'git pull'을 실패했습니다."
    Language
Dutch      -> Doc AnsiStyle
"Het uitvoeren van ‘git pull’ om de nieuwste bestanden op te halen is mislukt."
    Language
_          -> Doc AnsiStyle
"Failed to 'git pull' the latest updates."

------------------------------
-- Aura/Dependencies functions
------------------------------
-- NEEDS UPDATE TO MATCH NEW ENGLISH
getRealPkgConflicts_1 :: PkgName -> PkgName -> Text -> Text -> Language -> Doc AnsiStyle
getRealPkgConflicts_1 :: PkgName -> PkgName -> Text -> Text -> Language -> Doc AnsiStyle
getRealPkgConflicts_1 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle)
-> (PkgName -> Text) -> PkgName -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PkgName -> Text
pnName -> Doc AnsiStyle
prnt) (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle)
-> (PkgName -> Text) -> PkgName -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PkgName -> Text
pnName -> Doc AnsiStyle
p) (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt -> Doc AnsiStyle
r) (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt -> Doc AnsiStyle
d) = \case
    Language
Japanese   -> Doc AnsiStyle
"パッケージ" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"はバージョン" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"を要するが" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"一番最新のバージョンは" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"。"
    Language
Arabic     -> Doc AnsiStyle
prnt Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" الرزمة " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" تعتمد على النسخة " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" من " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" لكن أحدث نسخه هي"
    Language
Polish     -> Doc AnsiStyle
"Zależność " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" powinna być w wersji " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", ale najnowsza wersja to " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Croatian   -> Doc AnsiStyle
"Zavisnost " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" zahtjeva verziju " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", a najnovija dostupna verzija je " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Swedish    -> Doc AnsiStyle
"Beroendepaketet " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" kräver version " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" men den senaste versionen är " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
German     -> Doc AnsiStyle
"Die Abhängigkeit " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" verlangt Version " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", aber die neuste Version ist " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Spanish    -> Doc AnsiStyle
"La dependencia " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" requiere la versión " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" pero la versión más reciente es " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Portuguese -> Doc AnsiStyle
"A dependência " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" exige a versão " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" mas a versão mais recente é " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
French     -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" est une dépendance nécessitant la version " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", mais la plus récente est la version " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Russian    -> Doc AnsiStyle
"Зависимость " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" требует версию " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", однако самой последней версией является " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Italian    -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"è una dipendenza che necessita della versione " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", ma la più recente è la " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Serbian    -> Doc AnsiStyle
"Зависност " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" захтева верзију " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", али најновија верзија је " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Norwegian  -> Doc AnsiStyle
"Avhengigheten " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" krever versjon " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<>Doc AnsiStyle
", men den nyeste versjonen er " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Indonesia  -> Doc AnsiStyle
"Dependensi " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" meminta versi " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" namun versi paling baru adalah " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Chinese    -> Doc AnsiStyle
"依赖 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" 需要版本 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
",但是最新的版本是 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"。"
    Language
Esperanto  -> Doc AnsiStyle
"La pakaĵo, " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
prnt Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", dependas de versio " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" de " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", sed la plej nova versio estas " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Dutch      -> Doc AnsiStyle
prnt Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" is afhankelijk van versie " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" van " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", maar de nieuwste versie is " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Ukrainian  -> Doc AnsiStyle
"Залежність " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" потребує версію " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", проте останньою версією є " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Romanian   -> Doc AnsiStyle
"Pachetul " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
prnt Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" depinde de versiunea " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" al pachetului " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", dar cea mai recentă versiune este " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Vietnamese -> Doc AnsiStyle
"Gói " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
prnt Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" phụ thuộc vào bản " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" của " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", nhưng bản mới nhất là " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Czech      -> Doc AnsiStyle
"Balík " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
prnt Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" závisí na verzi " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" z " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", ale nejnovější verze je " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Korean     -> Doc AnsiStyle
prnt Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" 패키지는 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"의 버전 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"에 의존하지만 가장 최신 버전은 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"입니다."
    Language
_          -> Doc AnsiStyle
"The package " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
prnt Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" depends on version " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
d Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" of " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", but the most recent version is " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
r Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."

getRealPkgConflicts_2 :: PkgName -> Language -> Doc AnsiStyle
getRealPkgConflicts_2 :: PkgName -> Language -> Doc AnsiStyle
getRealPkgConflicts_2 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle)
-> (PkgName -> Text) -> PkgName -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PkgName -> Text
pnName -> Doc AnsiStyle
p) = \case
  Language
Japanese   -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"は無視されるパッケージ!`pacman.conf`を参考に。"
  Language
Arabic     -> Doc AnsiStyle
".الخاص بك `pacman.conf`انظر الى اﻟ !" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" ملف مجهول"
  Language
Polish     -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" jest ignorowany! Sprawdź plik `pacman.conf`."
  Language
Croatian   -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" je ignoriran paket! Provjerite svoj `pacman.conf`."
  Language
Swedish    -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" är ett ignorerat paket! Kolla din `pacman.conf`-fil."
  Language
German     -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" ist ein ignoriertes Paket! Siehe /etc/pacman.conf."
  Language
Spanish    -> Doc AnsiStyle
"¡" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" es un paquete ignorado! Revisa tu fichero `pacman.conf`."
  Language
Portuguese -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" é um pacote ignorado conforme configuração em `pacman.conf`!"
  Language
French     -> Doc AnsiStyle
"Le paquet " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" est ignoré. Vous devriez jeter un œil à votre `pacman.conf`."
  Language
Russian    -> Doc AnsiStyle
"Пакет " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" игнорируется! Проверьте ваш файл `pacman.conf`."
  Language
Italian    -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" è marcato come pacchetto ignorato all'interno del file `pacman.conf`."
  Language
Serbian    -> Doc AnsiStyle
"Пакет " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" је игнорисан! Видите ваш фајл „pacman.conf“."
  Language
Norwegian  -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" er en ignorert pakke! Sjekk din `pacman.conf`-fil."
  Language
Indonesia  -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" merupakan paket yang diabaikan! Lihat `pacman.conf` anda."
  Language
Chinese    -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" 是一个被忽略的包!请查看你的 `pacman.conf` 文件。"
  Language
Esperanto  -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" estas malatenta pakaĵo! Vidu vian `pacman.conf` dosieron."
  Language
Dutch      -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" wordt genegeerd! Bekijk uw `pacman.conf`-bestand."
  Language
Ukrainian  -> Doc AnsiStyle
"Пакунок " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" буде проігноровано! Перевірте ваш файл `pacman.conf`."
  Language
Romanian   -> Doc AnsiStyle
"Pachetul " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" este ignorat! Verificați fișierul `pacman.conf`."
  Language
Vietnamese -> Doc AnsiStyle
"Gói " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"đã bị bỏ qua! Hãy xem trong `pacman.conf` của bạn."
  Language
Czech      -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" je ignorovaný balíček! Podívejte se na svůj soubor `pacman.conf`."
  Language
Korean     -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"은(는) 무시된 패키지입니다! `pacman.conf`를 확인하시오."
  Language
_          -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" is an ignored package! See your `pacman.conf` file."

missingPkg_2 :: [DepError] -> Language -> Doc AnsiStyle
missingPkg_2 :: [DepError] -> Language -> Doc AnsiStyle
missingPkg_2 [DepError]
ps Language
l = [Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep ([Doc AnsiStyle] -> Doc AnsiStyle)
-> [Doc AnsiStyle] -> Doc AnsiStyle
forall a b. (a -> b) -> a -> b
$ (DepError -> Doc AnsiStyle) -> [DepError] -> [Doc AnsiStyle]
forall a b. (a -> b) -> [a] -> [b]
map (Language -> DepError -> Doc AnsiStyle
depError Language
l) [DepError]
ps

depError :: Language -> DepError -> Doc AnsiStyle
depError :: Language -> DepError -> Doc AnsiStyle
depError Language
_ (VerConflict Doc AnsiStyle
s) = Doc AnsiStyle
s
depError Language
_ (Ignored Doc AnsiStyle
s)     = Doc AnsiStyle
s
depError Language
l (NonExistant (PkgName Text
s) (PkgName Text
par)) = case Language
l of
  Language
Polish     -> Doc AnsiStyle
"Zależność " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"nie została znaleziona."
  Language
Arabic     -> Doc AnsiStyle
".غير موجود " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
par Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" من " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" الاعتماد"
  Language
Spanish    -> Doc AnsiStyle
"La dependencia " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" no pudo ser encontrada."
  Language
Portuguese -> Doc AnsiStyle
"A dependência " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" não foi encontrada."
  Language
Russian    -> Doc AnsiStyle
"Зависимость " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" не найдена."
  Language
Italian    -> Doc AnsiStyle
"Non è stato possibile trovare la dipendenza " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
  Language
Esperanto  -> Doc AnsiStyle
"La dependeco " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" de " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
par Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" ne povis troviĝi."
  Language
Dutch      -> Doc AnsiStyle
"De afhankelijkheid " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" van " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
par Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" kan niet worden gevonden."
  Language
Ukrainian  -> Doc AnsiStyle
"Залежність " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" не було знайдено."
  Language
Vietnamese -> Doc AnsiStyle
"Không thể tìm thấy các gói phụ thuộc của " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
  Language
Czech      -> Doc AnsiStyle
"Nebyla nalezena závislost " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" z " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
par Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
  Language
Korean     -> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
par Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"의 종속성 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"을(를) 찾을 수 없습니다."
  Language
_          -> Doc AnsiStyle
"The dependency " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" of " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
par Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" couldn't be found."

depError Language
l (BrokenProvides (PkgName Text
pkg) (Provides (PkgName Text
pro)) (PkgName Text
n)) = case Language
l of
  Language
Arabic     -> Doc AnsiStyle
"." Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" اللتي تقدم ," Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" تحتاج" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pkg Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" الرزمة"
  Language
Spanish    -> Doc AnsiStyle
"El paquete " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pkg Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" necesita " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" que proporciona " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
  Language
Russian    -> Doc AnsiStyle
"Пакету " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pkg Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" требуется " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", предоставляющий " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
  Language
Esperanto  -> Doc AnsiStyle
"La pakaĵo, " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pkg Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" bezonas " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", kiu donas " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
  Language
Italian    -> Doc AnsiStyle
"Il pacchetto " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pkg Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" ha bisogno di " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", che rende disponibile " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
  Language
Dutch      -> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pkg Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" is afhankelijk van " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", wat " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" bevat."
  Language
Ukrainian  -> Doc AnsiStyle
"Пакунку " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pkg Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" потрібен " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", який забезпечує " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
  Language
Romanian   -> Doc AnsiStyle
"Pachetul " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pkg Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" are nevoie de " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", care provizionează " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
  Language
Vietnamese -> Doc AnsiStyle
"Gói " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pkg Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" cần " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", để cung cấp " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
  Language
Czech      -> Doc AnsiStyle
"Balík " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pkg Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" potřebuje " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", který poskytuje " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
  Language
Korean     -> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pkg Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" 패키지는 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"를 제공하는 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"이(가) 필요합니다."
  Language
_          -> Doc AnsiStyle
"The package " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pkg Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" needs " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
", which provides " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."

missingPkg_3 :: Language -> Doc AnsiStyle
missingPkg_3 :: Language -> Doc AnsiStyle
missingPkg_3 = \case
  Language
Polish     -> Doc AnsiStyle
"Wystąpił problem podczas reorganizowania grafu zależności. Jeśli widzisz tą wiadomość, coś poszło bardzo nie tak."
  Language
Arabic     -> Doc AnsiStyle
".حدث خطا في اعادة تنظيم الرسم البياني التبعي. اذا رايت هذه الرسالة، فهناك مشكلة كبيرة"
  Language
Spanish    -> Doc AnsiStyle
"Se produjo un error al reorganizar el gráfico de dependencia. Si ves esto, algo está muy mal."
  Language
Esperanto  -> Doc AnsiStyle
"Eraro okazis kiam reorganizi la grafeo de dependeco. Io estas erarega."
  Language
Italian    -> Doc AnsiStyle
"C'è stato un errore nella riorganizzazione della gerarchia delle dipendenze. Se vedi questo messaggio, qualcosa è andato davvero storto."
  Language
Dutch      -> Doc AnsiStyle
"Er is een fout opgetreden tijdens het vernieuwen van de afhankelijkheidsgrafiek. Als u dit ziet, dan is er iets grondig mis."
  Language
Romanian   -> Doc AnsiStyle
"A fost o problemă reorganizând graful de dependențe. Dacă vedeți asta, e foarte rău."
  Language
Vietnamese -> Doc AnsiStyle
"Có lỗi trong quá trình xây dựng biểu đồ gói phụ thuộc. Nếu bạn thấy điều này, có gì đó không đúng."
  Language
Czech      -> Doc AnsiStyle
"Při reorganizaci grafu závislostí došlo k chybě. Pokud vidíte toto, něco je velmi špatně."
  Language
Korean     -> Doc AnsiStyle
"종속성 그래프를 재구성하는 동안 오류가 발생했습니다."
  Language
_          -> Doc AnsiStyle
"There was an error reorganizing the dependency graph. If you see this, something is very wrong."

missingPkg_4 :: [NonEmpty PkgName] -> Language -> Doc AnsiStyle
missingPkg_4 :: [NonEmpty PkgName] -> Language -> Doc AnsiStyle
missingPkg_4 [NonEmpty PkgName]
pns = \case
  Language
Polish     -> [Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep ([Doc AnsiStyle] -> Doc AnsiStyle)
-> [Doc AnsiStyle] -> Doc AnsiStyle
forall a b. (a -> b) -> a -> b
$ Doc AnsiStyle
"Następujące cykle zależności zostały wykryte:" Doc AnsiStyle -> [Doc AnsiStyle] -> [Doc AnsiStyle]
forall a. a -> [a] -> [a]
: [Doc AnsiStyle]
forall ann. [Doc ann]
pns'
  Language
Arabic     -> [Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep ([Doc AnsiStyle] -> Doc AnsiStyle)
-> [Doc AnsiStyle] -> Doc AnsiStyle
forall a b. (a -> b) -> a -> b
$ [Doc AnsiStyle]
forall ann. [Doc ann]
pns' [Doc AnsiStyle] -> [Doc AnsiStyle] -> [Doc AnsiStyle]
forall a. Semigroup a => a -> a -> a
<> [Doc AnsiStyle
":تم اكتشاف دورات التبعية التالية"]
  Language
Spanish    -> [Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep ([Doc AnsiStyle] -> Doc AnsiStyle)
-> [Doc AnsiStyle] -> Doc AnsiStyle
forall a b. (a -> b) -> a -> b
$ Doc AnsiStyle
"Se detectaron los siguientes ciclos de dependencia:" Doc AnsiStyle -> [Doc AnsiStyle] -> [Doc AnsiStyle]
forall a. a -> [a] -> [a]
: [Doc AnsiStyle]
forall ann. [Doc ann]
pns'
  Language
Italian    -> [Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep ([Doc AnsiStyle] -> Doc AnsiStyle)
-> [Doc AnsiStyle] -> Doc AnsiStyle
forall a b. (a -> b) -> a -> b
$ Doc AnsiStyle
"Sono stati individuati i seguenti cicli di dipendenza:" Doc AnsiStyle -> [Doc AnsiStyle] -> [Doc AnsiStyle]
forall a. a -> [a] -> [a]
: [Doc AnsiStyle]
forall ann. [Doc ann]
pns'
  Language
Dutch      -> [Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep ([Doc AnsiStyle] -> Doc AnsiStyle)
-> [Doc AnsiStyle] -> Doc AnsiStyle
forall a b. (a -> b) -> a -> b
$ Doc AnsiStyle
"De volgende afhankelijkheidscycli zijn gedetecteerd:" Doc AnsiStyle -> [Doc AnsiStyle] -> [Doc AnsiStyle]
forall a. a -> [a] -> [a]
: [Doc AnsiStyle]
forall ann. [Doc ann]
pns'
  Language
Ukrainian  -> [Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep ([Doc AnsiStyle] -> Doc AnsiStyle)
-> [Doc AnsiStyle] -> Doc AnsiStyle
forall a b. (a -> b) -> a -> b
$ Doc AnsiStyle
"Було помічено цикл залежностей:" Doc AnsiStyle -> [Doc AnsiStyle] -> [Doc AnsiStyle]
forall a. a -> [a] -> [a]
: [Doc AnsiStyle]
forall ann. [Doc ann]
pns'
  Language
Romanian   -> [Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep ([Doc AnsiStyle] -> Doc AnsiStyle)
-> [Doc AnsiStyle] -> Doc AnsiStyle
forall a b. (a -> b) -> a -> b
$ Doc AnsiStyle
"Aceste cicluri de dependență a fost detectate:" Doc AnsiStyle -> [Doc AnsiStyle] -> [Doc AnsiStyle]
forall a. a -> [a] -> [a]
: [Doc AnsiStyle]
forall ann. [Doc ann]
pns'
  Language
Vietnamese -> [Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep ([Doc AnsiStyle] -> Doc AnsiStyle)
-> [Doc AnsiStyle] -> Doc AnsiStyle
forall a b. (a -> b) -> a -> b
$ Doc AnsiStyle
"Phát hiện chu kỳ gói phụ thuộc: " Doc AnsiStyle -> [Doc AnsiStyle] -> [Doc AnsiStyle]
forall a. a -> [a] -> [a]
: [Doc AnsiStyle]
forall ann. [Doc ann]
pns'
  Language
Czech      -> [Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep ([Doc AnsiStyle] -> Doc AnsiStyle)
-> [Doc AnsiStyle] -> Doc AnsiStyle
forall a b. (a -> b) -> a -> b
$ Doc AnsiStyle
"Byly zjištěny následující cykly závislostí:" Doc AnsiStyle -> [Doc AnsiStyle] -> [Doc AnsiStyle]
forall a. a -> [a] -> [a]
: [Doc AnsiStyle]
forall ann. [Doc ann]
pns'
  Language
Korean     -> [Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep ([Doc AnsiStyle] -> Doc AnsiStyle)
-> [Doc AnsiStyle] -> Doc AnsiStyle
forall a b. (a -> b) -> a -> b
$ Doc AnsiStyle
"다음과 같은 종속성 주기가 발견되었습니다:" Doc AnsiStyle -> [Doc AnsiStyle] -> [Doc AnsiStyle]
forall a. a -> [a] -> [a]
: [Doc AnsiStyle]
forall ann. [Doc ann]
pns'
  Language
_          -> [Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep ([Doc AnsiStyle] -> Doc AnsiStyle)
-> [Doc AnsiStyle] -> Doc AnsiStyle
forall a b. (a -> b) -> a -> b
$ Doc AnsiStyle
"The following dependency cycles were detected:" Doc AnsiStyle -> [Doc AnsiStyle] -> [Doc AnsiStyle]
forall a. a -> [a] -> [a]
: [Doc AnsiStyle]
forall ann. [Doc ann]
pns'
  where
    pns' :: [Doc ann]
    pns' :: [Doc ann]
pns' = (NonEmpty PkgName -> Doc ann) -> [NonEmpty PkgName] -> [Doc ann]
forall a b. (a -> b) -> [a] -> [b]
map ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
hsep ([Doc ann] -> Doc ann)
-> (NonEmpty PkgName -> [Doc ann]) -> NonEmpty PkgName -> Doc ann
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Doc ann) -> [Text] -> [Doc ann]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty ([Text] -> [Doc ann])
-> (NonEmpty PkgName -> [Text]) -> NonEmpty PkgName -> [Doc ann]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
L.intersperse Text
"=>" ([Text] -> [Text])
-> (NonEmpty PkgName -> [Text]) -> NonEmpty PkgName -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PkgName -> Text) -> [PkgName] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map PkgName -> Text
pnName ([PkgName] -> [Text])
-> (NonEmpty PkgName -> [PkgName]) -> NonEmpty PkgName -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty PkgName -> [PkgName]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) [NonEmpty PkgName]
pns

missingPkg_5 :: PkgName -> Language -> Doc AnsiStyle
missingPkg_5 :: PkgName -> Language -> Doc AnsiStyle
missingPkg_5 (PkgName Text
p) = \case
  Language
Polish     -> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" nie istnieje."
  Language
Arabic     -> Doc AnsiStyle
".ليس موجود " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p
  Language
Spanish    -> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" no existe."
  Language
Italian    -> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" non esiste."
  Language
Dutch      -> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" bestaat niet."
  Language
Ukrainian  -> Doc AnsiStyle
"Пакунок " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" не існує."
  Language
Romanian   -> Doc AnsiStyle
"Pachetul " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" nu există."
  Language
Vietnamese -> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" không tồn tại."
  Language
Czech      -> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" neexistuje."
  Language
Korean     -> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"은(는) 존재하지 않습니다."
  Language
_          -> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" does not exist."

-----------------
-- aura functions
-----------------
displayOutputLanguages_1 :: Language -> Doc AnsiStyle
displayOutputLanguages_1 :: Language -> Doc AnsiStyle
displayOutputLanguages_1 = \case
    Language
Japanese   -> Doc AnsiStyle
"aura は下記の言語に対応しています:"
    Language
Arabic     -> Doc AnsiStyle
":اللغات التالية موجودة"
    Language
Polish     -> Doc AnsiStyle
"Następujące języki są dostępne:"
    Language
Croatian   -> Doc AnsiStyle
"Dostupni su sljedeći jezici:"
    Language
Swedish    -> Doc AnsiStyle
"Följande språk är tillängliga:"
    Language
German     -> Doc AnsiStyle
"Die folgenden Sprachen sind verfügbar:"
    Language
Spanish    -> Doc AnsiStyle
"Los siguientes idiomas están disponibles:"
    Language
Portuguese -> Doc AnsiStyle
"Os seguintes idiomas estão disponíveis:"
    Language
French     -> Doc AnsiStyle
"Les langues suivantes sont disponibles :"
    Language
Russian    -> Doc AnsiStyle
"Доступны следующие языки:"
    Language
Italian    -> Doc AnsiStyle
"Sono disponibili le seguenti lingue:"
    Language
Serbian    -> Doc AnsiStyle
"Доступни су следећи језици:"
    Language
Norwegian  -> Doc AnsiStyle
"Følgende språk er tilgjengelig:"
    Language
Indonesia  -> Doc AnsiStyle
"Berikut ini adalah bahasa yang tersedia:"
    Language
Chinese    -> Doc AnsiStyle
"以下语言是可用的:"
    Language
Esperanto  -> Doc AnsiStyle
"La sekvaj lingvo estas disponebla:"
    Language
Dutch      -> Doc AnsiStyle
"De volgende talen zijn beschikbaar:"
    Language
Ukrainian  -> Doc AnsiStyle
"Доступні наступні мови:"
    Language
Romanian   -> Doc AnsiStyle
"Aceste pacheturi sunt disponibile:"
    Language
Vietnamese -> Doc AnsiStyle
"Ngôn ngữ khả dụng:"
    Language
Czech      -> Doc AnsiStyle
"K dispozici jsou následující jazyky:"
    Language
Korean     -> Doc AnsiStyle
"다음 언어는 이용 가능합니다:"
    Language
_          -> Doc AnsiStyle
"The following languages are available:"

----------------------------
-- Aura/Commands/A functions
----------------------------
-- NEEDS TRANSLATION
auraCheck_1 :: Language -> Doc AnsiStyle
auraCheck_1 :: Language -> Doc AnsiStyle
auraCheck_1 = \case
    Language
Japanese   -> Doc AnsiStyle
"Aura が更新されています。Auraだけ先に更新しますか?"
    Language
Arabic     -> Doc AnsiStyle
"موجود. هل تريد ان تحدث اولا؟ Aura تحديث الى"
    Language
Polish     -> Doc AnsiStyle
"Dostępna jest nowa wersja Aura. Czy chcesz ją najpierw aktualizować?"
    Language
Croatian   -> Doc AnsiStyle
"Dostupna je nova verzija Aura. Želite li prvo ažurirati?"
    Language
German     -> Doc AnsiStyle
"Ein Update für aura ist verfügbar. Dies zuerst aktualisieren?"
    Language
Spanish    -> Doc AnsiStyle
"Hay una actualización de aura disponible. ¿Deseas actualizar aura primero?"
    Language
Norwegian  -> Doc AnsiStyle
"En Aura-oppdatering er tilgjengelig. Oppdater den først?"
    Language
Portuguese -> Doc AnsiStyle
"Uma atualização para Aura está disponível. Deseja atualizar antes?"
    Language
French     -> Doc AnsiStyle
"Une mise à jour d'Aura est disponible. Voulez-vous la mettre à jour en premier ?"
    Language
Russian    -> Doc AnsiStyle
"Доступно обновление Aura. Обновить сперва её?"
    Language
Italian    -> Doc AnsiStyle
"È disponibile un nuovo aggiornamento per Aura. Eseguirlo subito?"
    Language
Indonesia  -> Doc AnsiStyle
"Pemutakhiran aura tersedia. Mutakhirkan aura dulu?"
    Language
Chinese    -> Doc AnsiStyle
"Aura 可以升级。先升级 aura?"
    Language
Swedish    -> Doc AnsiStyle
"Det finns en uppdatering tillgänglig till Aura. Vill du uppdatera Aura först?"
    Language
Esperanto  -> Doc AnsiStyle
"Ĝisdatigo de Aura estas disponebla. Ĉu ĝisdatigas ĝin?"
    Language
Dutch      -> Doc AnsiStyle
"Er is een update van Aura beschikbaar. Wilt u Aura nu bijwerken?"
    Language
Ukrainian  -> Doc AnsiStyle
"Доступно оновлення для Aura. Бажаєте оновити її першою?"
    Language
Romanian   -> Doc AnsiStyle
"O versiune nouă de Aura este disponibilă. Să se actualizeze înainte de toate?"
    Language
Vietnamese -> Doc AnsiStyle
"Đã có cập nhật cho Aura. Cập nhật?"
    Language
Czech      -> Doc AnsiStyle
"K dispozici aktualizace Aury. Nejprve ji aktualizovat?"
    Language
Korean     -> Doc AnsiStyle
"Aura의 최신버전이 있습니다. 업데이트를 하시겠습니까?"
    Language
_          -> Doc AnsiStyle
"Aura update available. Update it first?"

install_2 :: Language -> Doc AnsiStyle
install_2 :: Language -> Doc AnsiStyle
install_2 = \case
    Language
Japanese   -> Doc AnsiStyle
"適切なパッケージを入力してください。"
    Language
Arabic     -> Doc AnsiStyle
".لم يتم تحديد حزم صالحة"
    Language
Polish     -> Doc AnsiStyle
"Nie podano prawidłowych pakietów."
    Language
Croatian   -> Doc AnsiStyle
"Nije specificiran nijedan ispravan paket."
    Language
Swedish    -> Doc AnsiStyle
"Inga giltiga paket valda."
    Language
German     -> Doc AnsiStyle
"Keine gültigen Pakete angegeben."
    Language
Spanish    -> Doc AnsiStyle
"No se ha especificado ningún paquete válido."
    Language
Portuguese -> Doc AnsiStyle
"Nenhum pacote válido foi especificado."
    Language
French     -> Doc AnsiStyle
"Aucun paquet valide n'a été spécifié."
    Language
Russian    -> Doc AnsiStyle
"Валидные пакеты не указаны."
    Language
Italian    -> Doc AnsiStyle
"Nessun pacchetto valido specificato."
    Language
Serbian    -> Doc AnsiStyle
"Ниједан исправан пакет није специфициран."
    Language
Norwegian  -> Doc AnsiStyle
"Ingen gyldige pakker er valgte."
    Language
Indonesia  -> Doc AnsiStyle
"Tidak ada paket valid yang dispesifikkan."
    Language
Chinese    -> Doc AnsiStyle
"没有指定有效的包。"
    Language
Esperanto  -> Doc AnsiStyle
"Ne validajn pakaĵojn specifis"
    Language
Dutch      -> Doc AnsiStyle
"Er zijn geen geldige pakketten opgegeven."
    Language
Ukrainian  -> Doc AnsiStyle
"Валідні пакунки не вказані."
    Language
Romanian   -> Doc AnsiStyle
"Nu s-a specificat nici un pachet valabil."
    Language
Vietnamese -> Doc AnsiStyle
"Tên của gói được yêu cầu không đúng."
    Language
Czech      -> Doc AnsiStyle
"Nejsou zadány žádné platné balíčky."
    Language
Korean     -> Doc AnsiStyle
"유효한 패키지가 지정되지 않았습니다."
    Language
_          -> Doc AnsiStyle
"No valid packages specified."

install_3 :: Language -> Doc AnsiStyle
install_3 :: Language -> Doc AnsiStyle
install_3 = \case
    Language
Japanese   -> Doc AnsiStyle
"続行しますか?"
    Language
Arabic     -> Doc AnsiStyle
"هل تريد ان تكمل؟"
    Language
Turkish    -> Doc AnsiStyle
"Devam edilsin mi?"
    Language
Polish     -> Doc AnsiStyle
"Kontynuować?"
    Language
Croatian   -> Doc AnsiStyle
"Nastaviti?"
    Language
Swedish    -> Doc AnsiStyle
"Fortsätta?"
    Language
German     -> Doc AnsiStyle
"Fortsetzen?"
    Language
Spanish    -> Doc AnsiStyle
"¿Continuar?"
    Language
Portuguese -> Doc AnsiStyle
"Continuar?"
    Language
French     -> Doc AnsiStyle
"Continuer ?"
    Language
Russian    -> Doc AnsiStyle
"Продолжить?"
    Language
Italian    -> Doc AnsiStyle
"Continuare?"
    Language
Serbian    -> Doc AnsiStyle
"Наставити?"
    Language
Norwegian  -> Doc AnsiStyle
"Fortsett?"
    Language
Indonesia  -> Doc AnsiStyle
"Lanjut?"
    Language
Chinese    -> Doc AnsiStyle
"继续?"
    Language
Esperanto  -> Doc AnsiStyle
"Ĉu daŭrigi?"
    Language
Dutch      -> Doc AnsiStyle
"Wilt u doorgaan?"
    Language
Ukrainian  -> Doc AnsiStyle
"Продовжити?"
    Language
Romanian   -> Doc AnsiStyle
"Continuați?"
    Language
Vietnamese -> Doc AnsiStyle
"Tiếp tục?"
    Language
Czech      -> Doc AnsiStyle
"Pokračovat?"
    Language
Korean     -> Doc AnsiStyle
"계속하시겠습니까?"
    Language
_          -> Doc AnsiStyle
"Continue?"

install_4 :: Language -> Doc AnsiStyle
install_4 :: Language -> Doc AnsiStyle
install_4 = \case
    Language
Japanese   -> Doc AnsiStyle
"続行は意図的に阻止されました。"
    Language
Arabic     -> Doc AnsiStyle
".تم الغاء التثبيت يدويا"
    Language
Polish     -> Doc AnsiStyle
"Instalacja została przerwana przez użytkownika."
    Language
Croatian   -> Doc AnsiStyle
"Instalacija prekinuta od strane korisnika."
    Language
Swedish    -> Doc AnsiStyle
"Installationen avbröts manuellt."
    Language
German     -> Doc AnsiStyle
"Installation durch Benutzer abgebrochen."
    Language
Spanish    -> Doc AnsiStyle
"Instalación abortada manualmente."
    Language
Portuguese -> Doc AnsiStyle
"Instalação cancelada manualmente."
    Language
French     -> Doc AnsiStyle
"Installation manuelle annulée."
    Language
Russian    -> Doc AnsiStyle
"Пользователь прервал установку."
    Language
Italian    -> Doc AnsiStyle
"Installazione manuale interrotta."
    Language
Serbian    -> Doc AnsiStyle
"Инсталација је ручно прекинута."
    Language
Norwegian  -> Doc AnsiStyle
"Installasjonen ble avbrutt manuelt."
    Language
Indonesia  -> Doc AnsiStyle
"Instalasi dibatalkan secara paksa."
    Language
Chinese    -> Doc AnsiStyle
"手动安装已中止。"
    Language
Esperanto  -> Doc AnsiStyle
"Instalon ĉesigi permane"
    Language
Dutch      -> Doc AnsiStyle
"De installatie is handmatig afgebroken."
    Language
Ukrainian  -> Doc AnsiStyle
"Встановлення скасовано користувачем."
    Language
Romanian   -> Doc AnsiStyle
"Instalarea anulată manual."
    Language
Vietnamese -> Doc AnsiStyle
"Quá trình cài đặt được hủy."
    Language
Czech      -> Doc AnsiStyle
"Instalace byla ručně přerušena."
    Language
Korean     -> Doc AnsiStyle
"설치가 중지되었습니다."
    Language
_          -> Doc AnsiStyle
"Installation manually aborted."

install_5 :: Language -> Doc AnsiStyle
install_5 :: Language -> Doc AnsiStyle
install_5 = \case
    Language
Japanese   -> Doc AnsiStyle
"従属パッケージを確認中・・・"
    Language
Arabic     -> Doc AnsiStyle
".تحديد التبعيات"
    Language
Polish     -> Doc AnsiStyle
"Ustalanie zależności..."
    Language
Croatian   -> Doc AnsiStyle
"Određivanje zavisnosti..."
    Language
Swedish    -> Doc AnsiStyle
"Avgör beroenden..."
    Language
German     -> Doc AnsiStyle
"Bestimme Abhängigkeiten..."
    Language
Spanish    -> Doc AnsiStyle
"Determinando dependencias..."
    Language
Portuguese -> Doc AnsiStyle
"Determinando as dependências..."
    Language
French     -> Doc AnsiStyle
"Détermination des dépendances en cours…"
    Language
Russian    -> Doc AnsiStyle
"Определение зависимостей..."
    Language
Italian    -> Doc AnsiStyle
"Determinazione delle dipendenze..."
    Language
Serbian    -> Doc AnsiStyle
"Утврђивање зависности..."
    Language
Norwegian  -> Doc AnsiStyle
"Bestemmer avhengigheter..."
    Language
Indonesia  -> Doc AnsiStyle
"Menentukan dependensi..."
    Language
Chinese    -> Doc AnsiStyle
"确定依赖中..."
    Language
Esperanto  -> Doc AnsiStyle
"Difinas dependecojn..."
    Language
Dutch      -> Doc AnsiStyle
"Bezig met vaststellen van afhankelijkheden…"
    Language
Ukrainian  -> Doc AnsiStyle
"Визначення залежностей..."
    Language
Romanian   -> Doc AnsiStyle
"Se determin dependențele..."
    Language
Vietnamese -> Doc AnsiStyle
"Xác định các gói phụ thuộc..."
    Language
Czech      -> Doc AnsiStyle
"Určování závislostí..."
    Language
Korean     -> Doc AnsiStyle
"종속성 확인 중..."
    Language
_          -> Doc AnsiStyle
"Determining dependencies..."

-- 2014 December  7 @ 14:45 - NEEDS TRANSLATIONS
confirmIgnored_1 :: PkgName -> Language -> Doc AnsiStyle
confirmIgnored_1 :: PkgName -> Language -> Doc AnsiStyle
confirmIgnored_1 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle)
-> (PkgName -> Text) -> PkgName -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PkgName -> Text
pnName -> Doc AnsiStyle
p) = \case
    Language
Japanese   -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"は無視されるはずのパッケージです。それでも続行しますか?"
    Language
Arabic     -> Doc AnsiStyle
"تم تحديده كمجهول. هل تريد ان تحمل على أي حال؟ " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p
    Language
Polish     -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" jest oznaczony jako ignorowany. Zainstalować mimo tego?"
    Language
Spanish    -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" está marcado como ignorado. ¿Deseas instalarlo de todas formas?"
    Language
Portuguese -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" está marcado como Ignorado. Deseja instalar mesmo assim?"
    Language
Russian    -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" отмечен как игнорируемый. Всё равно установить?"
    Language
Italian    -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" è marcato come pacchetto ignorato. Installarlo comunque?"
    Language
Chinese    -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" 已被标记为忽略。仍然安装?"
    Language
Swedish    -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" är markerad som ignorerad. Vill du installera ändå?"
    Language
Esperanto  -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" estas markita kiel malatenta. Ĉu instali?"
    Language
Dutch      -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" is gemarkeerd als genegeerd. Wilt u het pakket toch installeren?"
    Language
Romanian   -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" e marcat ca ignorat. Să se instaleze oricum?"
    Language
Vietnamese -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" được đánh dấu là Bỏ qua. Vẫn cài đặt nó?"
    Language
Czech      -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" je označeno jako ignorováno. Přesto nainstalovat?"
    Language
Korean     -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"은(는) 무시됨으로 표시됩니다. 설치를 하시겠습니까?"
    Language
_          -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" is marked as Ignored. Install anyway?"

-- NEEDS UPDATE TO REFLECT CHANGED ENGLISH
reportNonPackages_1 :: Language -> Doc AnsiStyle
reportNonPackages_1 :: Language -> Doc AnsiStyle
reportNonPackages_1 = \case
    Language
Japanese   -> Doc AnsiStyle
"下記はAURパッケージではありません:"
    Language
Arabic     -> Doc AnsiStyle
".AURالرزمة التالية ليست من اﻟ"
    Language
Polish     -> Doc AnsiStyle
"To nie są pakiety AUR:"
    Language
Croatian   -> Doc AnsiStyle
"Ovo nisu AUR paketi:"
    Language
Swedish    -> Doc AnsiStyle
"Följande är inte paket:"
    Language
German     -> Doc AnsiStyle
"Folgende sind keine AUR-Pakete:"
    Language
Spanish    -> Doc AnsiStyle
"Los siguientes paquetes no son de AUR:"
    Language
Portuguese -> Doc AnsiStyle
"Os seguintes não são pacotes AUR:"
    Language
French     -> Doc AnsiStyle
"Les éléments suivants ne sont pas des paquets AUR :"
    Language
Russian    -> Doc AnsiStyle
"Ниже указано то, что не является пакетами AUR:"
    Language
Italian    -> Doc AnsiStyle
"I seguenti pacchetti non fanno parte dell'AUR:"
    Language
Serbian    -> Doc AnsiStyle
"Ово нису пакети:"
    Language
Norwegian  -> Doc AnsiStyle
"Det følgende er ikke AUR-pakker:"
    Language
Indonesia  -> Doc AnsiStyle
"Paket berikut ini bukan merupakan paket AUR:"
    Language
Chinese    -> Doc AnsiStyle
"以下软件不是 AUR 包:"
    Language
Esperanto  -> Doc AnsiStyle
"La sekvaj ne estas pakaĵoj de la AUR:"
    Language
Dutch      -> Doc AnsiStyle
"De volgende pakketten zijn geen AUR-pakketten:"
    Language
Ukrainian  -> Doc AnsiStyle
"Нижче вказано те, що не є пакунком AUR:"
    Language
Romanian   -> Doc AnsiStyle
"Aceste pachete nu se află pe AUR:"
    Language
Vietnamese -> Doc AnsiStyle
"Các gói sau không thuộc AUR:"
    Language
Czech      -> Doc AnsiStyle
"Následující nejsou balíčky AUR:"
    Language
Korean     -> Doc AnsiStyle
"AUR 패키지가 아닙니다:"
    Language
_          -> Doc AnsiStyle
"The following are not AUR packages:"

-- NEEDS TRANSLATION
reportUnneededPackages_1 :: Language -> Doc AnsiStyle
reportUnneededPackages_1 :: Language -> Doc AnsiStyle
reportUnneededPackages_1 = \case
    Language
Japanese   -> Doc AnsiStyle
"下記のパッケージは既にインストールされています:"
    Language
Arabic     -> Doc AnsiStyle
".الرزمة التالية مثبتة"
    Language
Polish     -> Doc AnsiStyle
"Następujące pakiety zostały już zainstalowane:"
    Language
Portuguese -> Doc AnsiStyle
"Os seguintes pacotes já estão instalados:"
    Language
Russian    -> Doc AnsiStyle
"Следующие пакеты уже установлены:"
    Language
Italian    -> Doc AnsiStyle
"I seguenti pacchetti sono già stati installati:"
    Language
German     -> Doc AnsiStyle
"Die folgenden Pakete sind bereits installiert:"
    Language
Spanish    -> Doc AnsiStyle
"Los siguientes paquetes ya están instalados:"
    Language
Chinese    -> Doc AnsiStyle
"以下包已被安装:"
    Language
Swedish    -> Doc AnsiStyle
"Följande paket är redan installerade:"
    Language
Esperanto  -> Doc AnsiStyle
"La sekvaj pakaĵoj jam instaliĝas:"
    Language
Dutch      -> Doc AnsiStyle
"De volgende pakketten zijn al geinstalleerd:"
    Language
Ukrainian  -> Doc AnsiStyle
"Наступні пакунки вже встановлені:"
    Language
Romanian   -> Doc AnsiStyle
"Aceste pachete sunt deja instalate:"
    Language
Vietnamese -> Doc AnsiStyle
"Các gói sau đã sẵn sàng cài đặt:"
    Language
Czech      -> Doc AnsiStyle
"Následující balíčky jsou již nainstalovány:"
    Language
Korean     -> Doc AnsiStyle
"아래 패키지는 이미 설치되어 있습니다:"
    Language
_          -> Doc AnsiStyle
"The following packages are already installed:"

reportPkgsToInstall_1 :: Language -> Doc AnsiStyle
reportPkgsToInstall_1 :: Language -> Doc AnsiStyle
reportPkgsToInstall_1 = \case
    Language
Japanese   -> Doc AnsiStyle
"Pacmanの従属パッケージ:"
    Language
Arabic     -> Doc AnsiStyle
":تبعيات المستودع"
    Language
Polish     -> Doc AnsiStyle
"Zależności z repozytoriów:"
    Language
Croatian   -> Doc AnsiStyle
"Zavisnosti iz repozitorija:"
    Language
Swedish    -> Doc AnsiStyle
"Beroenden ifrån lager:"
    Language
German     -> Doc AnsiStyle
"Abhängigkeiten in den Paketquellen:"
    Language
Spanish    -> Doc AnsiStyle
"Dependencias del repositorio:"
    Language
Portuguese -> Doc AnsiStyle
"Dependências no repositório:"
    Language
French     -> Doc AnsiStyle
"Dépendances du dépôt :"
    Language
Russian    -> Doc AnsiStyle
"Зависимости из репозитория:"
    Language
Italian    -> Doc AnsiStyle
"Dipendenze del repository:"
    Language
Serbian    -> Doc AnsiStyle
"Зависности из ризница:"
    Language
Norwegian  -> Doc AnsiStyle
"Avhengigheter fra depotet:"
    Language
Indonesia  -> Doc AnsiStyle
"Dependensi dari repositori:"
    Language
Chinese    -> Doc AnsiStyle
"仓库依赖:"
    Language
Esperanto  -> Doc AnsiStyle
"Dependecoj de deponejo:"
    Language
Dutch      -> Doc AnsiStyle
"Pakketbron-afhankelijkheden:"
    Language
Ukrainian  -> Doc AnsiStyle
"Залежності репозиторія:"
    Language
Romanian   -> Doc AnsiStyle
"Dependențe din repertorii:"
    Language
Vietnamese -> Doc AnsiStyle
"Các repo phụ thuộc:"
    Language
Czech      -> Doc AnsiStyle
"Závislosti úložiště:"
    Language
Korean     -> Doc AnsiStyle
"리포지토리 종속성:"
    Language
_          -> Doc AnsiStyle
"Repository dependencies:"

-- NEEDS AN UPDATE
reportPkgsToInstall_2 :: Language -> Doc AnsiStyle
reportPkgsToInstall_2 :: Language -> Doc AnsiStyle
reportPkgsToInstall_2 = \case
    Language
Japanese   -> Doc AnsiStyle
"AURのパッケージ:"
    Language
Arabic     -> Doc AnsiStyle
":AURرزمةاﻟ"
    Language
Polish     -> Doc AnsiStyle
"Pakiety AUR:"
    Language
Turkish    -> Doc AnsiStyle
"AUR Paketleri:"
    Language
Croatian   -> Doc AnsiStyle
"AUR Paketi:"
    Language
German     -> Doc AnsiStyle
"AUR Pakete:"
    Language
Spanish    -> Doc AnsiStyle
"AUR Paquetes:"
    Language
Norwegian  -> Doc AnsiStyle
"AUR Pakker:"
    Language
Italian    -> Doc AnsiStyle
"AUR Pacchetti:"
    Language
Portuguese -> Doc AnsiStyle
"AUR Pacotes:"
    Language
French     -> Doc AnsiStyle
"AUR Paquets :"
    Language
Russian    -> Doc AnsiStyle
"AUR Пакеты:"
    Language
Indonesia  -> Doc AnsiStyle
"AUR Paket:"
    Language
Chinese    -> Doc AnsiStyle
"AUR 包:"
    Language
Swedish    -> Doc AnsiStyle
"AUR Paket:"
    Language
Esperanto  -> Doc AnsiStyle
"Pakaĵoj de AUR:"
    Language
Dutch      -> Doc AnsiStyle
"AUR-pakketten:"
    Language
Ukrainian  -> Doc AnsiStyle
"Пакунки AUR:"
    Language
Romanian   -> Doc AnsiStyle
"Pachete din AUR:"
    Language
Vietnamese -> Doc AnsiStyle
"Gói AUR:"
    Language
Czech      -> Doc AnsiStyle
"Balíčky AUR:"
    Language
Korean     -> Doc AnsiStyle
"AUR 패키지:"
    Language
_          -> Doc AnsiStyle
"AUR Packages:"

reportPkgsToInstall_3 :: Language -> Doc AnsiStyle
reportPkgsToInstall_3 :: Language -> Doc AnsiStyle
reportPkgsToInstall_3 = \case
    Language
Japanese   -> Doc AnsiStyle
"AURの従属パッケージ:"
    Language
Arabic     -> Doc AnsiStyle
":AURتبعيات اﻟ"
    Language
Polish     -> Doc AnsiStyle
"Zależności z AUR:"
    Language
Croatian   -> Doc AnsiStyle
"Zavisnosti iz AUR-a:"
    Language
Swedish    -> Doc AnsiStyle
"Beroenden ifrån AUR:"
    Language
German     -> Doc AnsiStyle
"Abhängigkeiten im AUR:"
    Language
Spanish    -> Doc AnsiStyle
"Dependencias en AUR:"
    Language
Portuguese -> Doc AnsiStyle
"Dependências no AUR:"
    Language
French     -> Doc AnsiStyle
"Dépendances AUR\xa0:"
    Language
Russian    -> Doc AnsiStyle
"Зависимости из AUR:"
    Language
Italian    -> Doc AnsiStyle
"Dipendenze nell'AUR:"
    Language
Serbian    -> Doc AnsiStyle
"Зависности из AUR-а:"
    Language
Norwegian  -> Doc AnsiStyle
"Avhengigheter fra AUR:"
    Language
Esperanto  -> Doc AnsiStyle
"Dependencoj de AUR:"
    Language
Dutch      -> Doc AnsiStyle
"AUR-afhankelijkheden:"
    Language
Ukrainian  -> Doc AnsiStyle
"Залежності в AUR:"
    Language
Romanian   -> Doc AnsiStyle
"Dependențe din AUR:"
    Language
Vietnamese -> Doc AnsiStyle
"Gói phụ thuộc của AUR:"
    Language
Czech      -> Doc AnsiStyle
"Závislosti AUR:"
    Language
Korean     -> Doc AnsiStyle
"AUR 종속성:"
    Language
_          -> Doc AnsiStyle
"AUR dependencies:"

-- NEEDS TRANSLATION
reportPkgbuildDiffs_1 :: PkgName -> Language -> Doc AnsiStyle
reportPkgbuildDiffs_1 :: PkgName -> Language -> Doc AnsiStyle
reportPkgbuildDiffs_1 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle)
-> (PkgName -> Text) -> PkgName -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PkgName -> Text
pnName -> Doc AnsiStyle
p) = \case
    Language
Japanese   -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"のPKGBUILDはまだ保存されていません。"
    Language
Arabic     -> Doc AnsiStyle
".مخزن الان PKGBUILD لا يوجد" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p
    Language
Polish     -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" nie ma jeszcze przechowywanego pliku PKGBUILD."
    Language
Croatian   -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" još nema pohranjen PKGBUILD."
    Language
German     -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" hat noch keinen gespeicherten PKGBUILD."
    Language
Spanish    -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" no tiene un PKGBUILD almacenado aún."
    Language
Portuguese -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" não possui PKGBUILD."
    Language
French     -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" n'a pas encore de PKGBUILD enregistré."
    Language
Russian    -> Doc AnsiStyle
"У " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" ещё нет сохраненного PKGBUILD."
    Language
Italian    -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" non ci sono ancora PKGBUILD salvati"
    Language
Serbian    -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" још нема похрањен PKGBUILD."
    Language
Norwegian  -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" har ingen PKGBUILD ennå."
    Language
Indonesia  -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" tidak mempunyai PKGBUILD yang tersimpan untuk saat ini."
    Language
Chinese    -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" 还没有保存的 PKGBUILD。"
    Language
Swedish    -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" har ännu ingen PKGBUILD."
    Language
Esperanto  -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" ne havas PKGBUILD jam."
    Language
Dutch      -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" heeft nog geen opgeslagen PKGBUILD."
    Language
Ukrainian  -> Doc AnsiStyle
"В " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" ще не зберігається PKGBUILD."
    Language
Romanian   -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" încă nu are un PKGBUILD descărcat."
    Language
Vietnamese -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" không có sẵn PKGBUILD."
    Language
Czech      -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" ještě nemá uložený PKGBUILD."
    Language
Korean     -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"의 PKGBUILD는 저장되지 않았습니다."
    Language
_          -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" has no stored PKGBUILD yet."

-- NEEDS TRANSLATION
reportPkgbuildDiffs_3 :: PkgName -> Language -> Doc AnsiStyle
reportPkgbuildDiffs_3 :: PkgName -> Language -> Doc AnsiStyle
reportPkgbuildDiffs_3 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle)
-> (PkgName -> Text) -> PkgName -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PkgName -> Text
pnName -> Doc AnsiStyle
p) = \case
    Language
Japanese   -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"のPKGBUILD変更報告:"
    Language
Arabic     -> Doc AnsiStyle
"قد تغير PKGBUILD " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p
    Language
Polish     -> Doc AnsiStyle
"Zmiany w PKGBUILD dla " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
":"
    Language
Croatian   -> Doc AnsiStyle
"Promjene u PKGBUILD-u za " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
":"
    Language
German     -> Doc AnsiStyle
"PKGBUILD-Änderungen von " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
":"
    Language
Spanish    -> Doc AnsiStyle
"Cambios en el PKGBUILD de " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
":"
    Language
Portuguese -> Doc AnsiStyle
"Mudanças no PKGBUILD de " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
":"
    Language
Russian    -> Doc AnsiStyle
"Изменения, вносимые " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" PKGBUILD:"
    Language
French     -> Doc AnsiStyle
"Changements du PKGBUILD de " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" :"
    Language
Italian    -> Doc AnsiStyle
"Cambiamenti nel PKGBUILD del pacchetto " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<>Doc AnsiStyle
":"
    Language
Serbian    -> Doc AnsiStyle
"Промене PKGBUILD-a за " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
":"
    Language
Norwegian  -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"'s endringer i PKGBUILD:"
    Language
Indonesia  -> Doc AnsiStyle
"Perubahan PKGBUILD " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
":"
    Language
Chinese    -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" 的 PKGBUILD 变化:"
    Language
Swedish    -> Doc AnsiStyle
"Förändringar i PKGBUILD för " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
":"
    Language
Esperanto  -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" PKGBUILD ŝanĝoj:"
    Language
Dutch      -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" PKGBUILD-aanpassingen:"
    Language
Ukrainian  -> Doc AnsiStyle
"Зміни PKGBUILD в " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
":"
    Language
Romanian   -> Doc AnsiStyle
"Schimbări in PKGBUILD pentru " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
":"
    Language
Vietnamese -> Doc AnsiStyle
"Thay đổi trong PKGBUILD của " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
":"
    Language
Czech      -> Doc AnsiStyle
"Změny PKGBUILD v " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
":"
    Language
Korean     -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"의 PKGBUILD 변경 사항:"
    Language
_          -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" PKGBUILD changes:"

-- NEEDS TRANSLATION
reportPkgsToUpgrade_1 :: Language -> Doc AnsiStyle
reportPkgsToUpgrade_1 :: Language -> Doc AnsiStyle
reportPkgsToUpgrade_1 = \case
    Language
Japanese   -> Doc AnsiStyle
"アップグレードするAURパッケージ:"
    Language
Arabic     -> Doc AnsiStyle
"للتحديث AURرزمة اﻟ"
    Language
Polish     -> Doc AnsiStyle
"Pakiety z AUR do zaktualizowania:"
    Language
Croatian   -> Doc AnsiStyle
"AUR paketi za nadogradnju:"
    Language
Swedish    -> Doc AnsiStyle
"AUR-paket att uppgradera:"
    Language
German     -> Doc AnsiStyle
"Zu aktualisierendes AUR-Paket:"
    Language
Spanish    -> Doc AnsiStyle
"Paquetes de AUR a actualizar:"
    Language
Portuguese -> Doc AnsiStyle
"Pacotes do AUR para atualizar:"
    Language
French     -> Doc AnsiStyle
"Paquets AUR à mettre à jour :"
    Language
Russian    -> Doc AnsiStyle
"Пакеты AUR, готовые для обновления:"
    Language
Italian    -> Doc AnsiStyle
"Pacchetti dell'AUR da aggiornare:"
    Language
Serbian    -> Doc AnsiStyle
"Пакети из AUR-а за надоградњу:"
    Language
Norwegian  -> Doc AnsiStyle
"AUR-pakker å oppgradere:"
    Language
Indonesia  -> Doc AnsiStyle
"Paket AUR yang akan ditingkatkan:"
    Language
Chinese    -> Doc AnsiStyle
"要升级的 AUR 包:"
    Language
Esperanto  -> Doc AnsiStyle
"Pakaĵoj de AUR ĝisdatigi:"
    Language
Dutch      -> Doc AnsiStyle
"Bij te werken AUR-pakketten:"
    Language
Ukrainian  -> Doc AnsiStyle
"Пакунки AUR, готові для оновлення:"
    Language
Romanian   -> Doc AnsiStyle
"Pachete din AUR de actualizat:"
    Language
Vietnamese -> Doc AnsiStyle
"Cập nhật các gói AUR:"
    Language
Czech      -> Doc AnsiStyle
"Balíčky AUR k aktualizaci:"
    Language
Korean     -> Doc AnsiStyle
"업그레이드할 AUR 패키지:"
    Language
_          -> Doc AnsiStyle
"AUR Packages to upgrade:"

-- NEEDS UPDATING
reportBadDowngradePkgs_1 :: Language -> Doc AnsiStyle
reportBadDowngradePkgs_1 :: Language -> Doc AnsiStyle
reportBadDowngradePkgs_1 = \case
    Language
Japanese   -> Doc AnsiStyle
"このパッケージはキャッシュには入っていないので、ダウングレードできません。"
    Language
Arabic     -> Doc AnsiStyle
"ما يلي ليس له إصدارات في ذاكرة التخزين المؤقت ، وبالتالي لا يمكن الرجوع إلى الإصدار السابق."
    Language
Polish     -> Doc AnsiStyle
"Poniższe pakiety nie są zainstalowane i nie mogą być zainstalowane w starszej wersji:"
    Language
Croatian   -> Doc AnsiStyle
"Sljedeći paketi nisu instalirani te se stoga ne mogu vratiti na stare verzije:"
    Language
Swedish    -> Doc AnsiStyle
"Följande paket är inte installerade, och kan därför inte bli nergraderade:"
    Language
German     -> Doc AnsiStyle
"Folgende Pakete sind in keiner Version im Cache und können daher nicht gedowngradet werden:"
    Language
Spanish    -> Doc AnsiStyle
"Los siguientes paquetes no tienen versiones en la caché, por lo que no se pueden bajar a versiones anteriores:"
    Language
Portuguese -> Doc AnsiStyle
"Os seguintes pacotes não possuem versões no cache, logo não podem retornar a uma versão anterior:"
    Language
French     -> Doc AnsiStyle
"Aucune version des paquets suivants n'est présente dans le cache ; ils ne peuvent pas être mis à niveau à une version antérieure :"
    Language
Russian    -> Doc AnsiStyle
"Следующих пакетов нет в кэше. Следовательно, они не могут быть откачены к старой версии:"
    Language
Italian    -> Doc AnsiStyle
"Nessuna versione dei seguenti pacchetti è disponibile nella cache, perciò non è possibile riportarli ad una versione precedente:"
    Language
Serbian    -> Doc AnsiStyle
"Следећи пакети нису ни инсталирани, те се не могу вратити на старију верзију:"
    Language
Norwegian  -> Doc AnsiStyle
"Følgende pakker har ingen versjoner i cache, og kan derfor ikke bli nedgradert:"
    Language
Indonesia  -> Doc AnsiStyle
"Berikut ini tidak mempunyai versi pada cache, sehingga tidak akan diturunkan:"
    Language
Chinese    -> Doc AnsiStyle
"以下包在缓存中没有版本,所以无法被降级:"
    Language
Esperanto  -> Doc AnsiStyle
"La sekvaj pakaĵoj havas ne kaŝmemorigitajn versiojn, do ĝi ne povas malpromociigi:"
    Language
Dutch      -> Doc AnsiStyle
"De volgende pakketten zijn niet gecachet en kunnen daarom niet worden afgewaardeerd."
    Language
Ukrainian  -> Doc AnsiStyle
"Наступних пакунків немає в кеші. Отже, вони не можуть відкотитися до старої версії:"
    Language
Romanian   -> Doc AnsiStyle
"Aceste pachete nu au nici o versiune disponibilă în cache, așa că nu pot fi retrogradate:"
    Language
Vietnamese -> Doc AnsiStyle
"Những gói sau không có bản nào trong cache, vì vậy không thể hạ cấp:"
    Language
Czech      -> Doc AnsiStyle
"Následující nemají žádné verze v mezipaměti, a proto je nelze downgradovat:"
    Language
Korean     -> Doc AnsiStyle
"이 패키지는 캐시에 저장된 다른 버전이 없으므로 다운그레이드를 할 수 없습니다."
    Language
_          -> Doc AnsiStyle
"The following have no versions in the cache, and thus can’t be downgraded:"

reportBadDowngradePkgs_2 :: PkgName -> Language -> Doc AnsiStyle
reportBadDowngradePkgs_2 :: PkgName -> Language -> Doc AnsiStyle
reportBadDowngradePkgs_2 (PkgName Text
p) = \case
  Language
Spanish    -> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"no tiene una versión en la caché."
  Language
Arabic     -> Doc AnsiStyle
".ليس  لديه اصدار في الذاكرة التخزين الموقت" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
p
  Language
Italian    -> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"non ha alcuna versione nella cache."
  Language
Dutch      -> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"is niet gecachet."
  Language
Ukrainian  -> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"не має версії в кеші."
  Language
Romanian   -> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"nu are nici o versiune în cache."
  Language
Vietnamese -> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"không có bản nào trong cache."
  Language
Czech      -> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"nemá žádnou verzi v mezipaměti."
  Language
Korean     -> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"의 캐시에는 저장된 다른 버전이 없습니다."
  Language
_          -> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"has no version in the cache."

upgradeAURPkgs_1 :: Language -> Doc AnsiStyle
upgradeAURPkgs_1 :: Language -> Doc AnsiStyle
upgradeAURPkgs_1 = \case
    Language
Japanese   -> Doc AnsiStyle
"パッケージ情報をダウンロード中・・・"
    Language
Arabic     -> Doc AnsiStyle
"...احضار معلومات الحزمة"
    Language
Polish     -> Doc AnsiStyle
"Pobieranie informacji o pakietach..."
    Language
Croatian   -> Doc AnsiStyle
"Preuzimanje podataka o paketima..."
    Language
Swedish    -> Doc AnsiStyle
"Hämtar paketinformation..."
    Language
German     -> Doc AnsiStyle
"Rufe Paketinformationen ab..."
    Language
Spanish    -> Doc AnsiStyle
"Obteniendo información de los paquetes..."
    Language
Portuguese -> Doc AnsiStyle
"Obtendo informação dos pacotes..."
    Language
French     -> Doc AnsiStyle
"Obtention des informations des paquets en cours…"
    Language
Russian    -> Doc AnsiStyle
"Сборка информации о пакетах..."
    Language
Italian    -> Doc AnsiStyle
"Ottenimento di informazioni sui pacchetti..."
    Language
Serbian    -> Doc AnsiStyle
"Преузимање информација о пакетима..."
    Language
Norwegian  -> Doc AnsiStyle
"Henter pakkeinformasjon..."
    Language
Indonesia  -> Doc AnsiStyle
"Mengambil informasi paket..."
    Language
Chinese    -> Doc AnsiStyle
"正在获取包信息..."
    Language
Esperanto  -> Doc AnsiStyle
"Venigas informacion de pakaĵoj..."
    Language
Dutch      -> Doc AnsiStyle
"Bezig met ophalen van pakketinformatie…"
    Language
Ukrainian  -> Doc AnsiStyle
"Збираємо інформацію про пакунок..."
    Language
Romanian   -> Doc AnsiStyle
"Se obțin informații despre pachete..."
    Language
Vietnamese -> Doc AnsiStyle
"Cập nhật thông tin của gói..."
    Language
Czech      -> Doc AnsiStyle
"Načítání informací o balíčku..."
    Language
Korean     -> Doc AnsiStyle
"패키지 정보 가져오는 중..."
    Language
_          -> Doc AnsiStyle
"Fetching package information..."

upgradeAURPkgs_2 :: Language -> Doc AnsiStyle
upgradeAURPkgs_2 :: Language -> Doc AnsiStyle
upgradeAURPkgs_2 = \case
    Language
Japanese   -> Doc AnsiStyle
"バージョンを比較中・・・"
    Language
Arabic     -> Doc AnsiStyle
"...مقارنة اصدارات الحزمة"
    Language
Polish     -> Doc AnsiStyle
"Porównywanie wersji pakietów..."
    Language
Croatian   -> Doc AnsiStyle
"Uspoređivanje verzija paketa..."
    Language
Swedish    -> Doc AnsiStyle
"Jämför paket-versioner..."
    Language
German     -> Doc AnsiStyle
"Vergleiche Paketversionen..."
    Language
Spanish    -> Doc AnsiStyle
"Comparando versiones de los paquetes..."
    Language
Portuguese -> Doc AnsiStyle
"Comparando versões dos pacotes..."
    Language
French     -> Doc AnsiStyle
"Comparaison des versions des paquets en cours…"
    Language
Russian    -> Doc AnsiStyle
"Сравнение версий пакетов..."
    Language
Italian    -> Doc AnsiStyle
"Esecuzione di un confronto fra le versioni dei pacchetti..."
    Language
Serbian    -> Doc AnsiStyle
"Упоређивање верзија пакета..."
    Language
Norwegian  -> Doc AnsiStyle
"Sammenligner pakkeversjoner..."
    Language
Indonesia  -> Doc AnsiStyle
"Membandingkan versi paket..."
    Language
Chinese    -> Doc AnsiStyle
"正在比较包的版本..."
    Language
Esperanto  -> Doc AnsiStyle
"Komparas versiojn de pakaĵoj..."
    Language
Dutch      -> Doc AnsiStyle
"Bezig met vergelijken van pakketversies…"
    Language
Ukrainian  -> Doc AnsiStyle
"Порівнюємо версії пакунків..."
    Language
Romanian   -> Doc AnsiStyle
"Se compar versiunile pacheturilor..."
    Language
Vietnamese -> Doc AnsiStyle
"So sánh phiên bản của gói..."
    Language
Czech      -> Doc AnsiStyle
"Porovnání verzí balíčků..."
    Language
Korean     -> Doc AnsiStyle
"패키지 버전 비교 중..."
    Language
_          -> Doc AnsiStyle
"Comparing package versions..."

upgradeAURPkgs_3 :: Language -> Doc AnsiStyle
upgradeAURPkgs_3 :: Language -> Doc AnsiStyle
upgradeAURPkgs_3 = \case
    Language
Japanese   -> Doc AnsiStyle
"アップグレードは必要ありません。"
    Language
Arabic     -> Doc AnsiStyle
".AURلا يلزم تحديث حزمة اﻟ"
    Language
Polish     -> Doc AnsiStyle
"Nie jest wymagana aktualizacja pakietów z AUR."
    Language
Croatian   -> Doc AnsiStyle
"Svi AUR paketi su ažurirani."
    Language
Swedish    -> Doc AnsiStyle
"Inga AUR-paketsuppgraderingar behövs."
    Language
German     -> Doc AnsiStyle
"Keine Aktualisierungen für AUR-Paket notwendig."
    Language
Spanish    -> Doc AnsiStyle
"No es necesario actualizar paquetes de AUR."
    Language
Portuguese -> Doc AnsiStyle
"Nenhum pacote do AUR precisa de atualização."
    Language
French     -> Doc AnsiStyle
"Aucune mise à jour de paquet AUR n'est nécessaire."
    Language
Russian    -> Doc AnsiStyle
"Обновление пакетов из AUR не требуется."
    Language
Italian    -> Doc AnsiStyle
"Nessun pacchetto dell'AUR necessita di aggiornamenti."
    Language
Serbian    -> Doc AnsiStyle
"Ажурирање пакета из AUR-а није потребно."
    Language
Norwegian  -> Doc AnsiStyle
"Ingen pakkeoppgradering fra AUR nødvendig."
    Language
Indonesia  -> Doc AnsiStyle
"Tidak ada peningkatan AUR yang dibutuhkan."
    Language
Chinese    -> Doc AnsiStyle
"没有需要升级的 AUR 包。"
    Language
Esperanto  -> Doc AnsiStyle
"Ne ĝisdatigoj de pakaĵoj de AUR necesas."
    Language
Dutch      -> Doc AnsiStyle
"Er hoeven geen AUR-pakketten te worden bijgewerkt."
    Language
Ukrainian  -> Doc AnsiStyle
"Пакунки AUR не потребують оновлення."
    Language
Romanian   -> Doc AnsiStyle
"Nu e nevoie să se actualizeze nici un pachet din AUR."
    Language
Vietnamese -> Doc AnsiStyle
"Không có cập nhật cho các gói AUR."
    Language
Czech      -> Doc AnsiStyle
"Není nutné žádné aktualizace balíčku AUR."
    Language
Korean     -> Doc AnsiStyle
"업그레이드가 필요하지 않습니다."
    Language
_          -> Doc AnsiStyle
"No AUR package upgrades necessary."

removeMakeDepsAfter_1 :: Language -> Doc AnsiStyle
removeMakeDepsAfter_1 :: Language -> Doc AnsiStyle
removeMakeDepsAfter_1 = \case
    Language
Japanese   -> Doc AnsiStyle
"あと片付け。必要ないパッケージを削除:"
    Language
Arabic     -> Doc AnsiStyle
"...التي لا لزوم لها makeازالة التبعيات اﻟ"
    Language
Polish     -> Doc AnsiStyle
"Usuwanie niepotrzebnych zależności potrzebnych do budowy..."
    Language
Croatian   -> Doc AnsiStyle
"Uklanjanje nepotrebnih zavisnosti vezanih uz izgradnju..."
    Language
Swedish    -> Doc AnsiStyle
"Tar bort obehövda beroenden för `make`..."
    Language
German     -> Doc AnsiStyle
"Entferne nicht benötigte make-Abhängigkeiten..."
    Language
Spanish    -> Doc AnsiStyle
"Removiendo dependencias `make` innecesarias..."
    Language
Portuguese -> Doc AnsiStyle
"Removendo dependências `make` desnecessárias..."
    Language
French     -> Doc AnsiStyle
"Suppression des dépendances inutiles…"
    Language
Russian    -> Doc AnsiStyle
"Удаление ненужных зависимостей make..."
    Language
Italian    -> Doc AnsiStyle
"Rimozione delle dipendenze utilizzate per la compilazione..."
    Language
Serbian    -> Doc AnsiStyle
"Уклањање непотребних зависности за изградњу..."
    Language
Norwegian  -> Doc AnsiStyle
"Fjerner unødvendige make-avhengigheter..."
    Language
Indonesia  -> Doc AnsiStyle
"Menghapus dependensi `make` yang tidak dibutuhkan..."
    Language
Chinese    -> Doc AnsiStyle
"移除不需要的 make 依赖..."
    Language
Esperanto  -> Doc AnsiStyle
"Forigas nenecesajn dependecojn de make..."
    Language
Dutch      -> Doc AnsiStyle
"Bezig met verwijderen van onnodige make-afhankelijkheden…"
    Language
Ukrainian  -> Doc AnsiStyle
"Видаляємо непотрібні залежності make..."
    Language
Romanian   -> Doc AnsiStyle
"Se șterg dependențele de compilare inutile..."
    Language
Vietnamese -> Doc AnsiStyle
"Loại bỏ các gói phụ thuộc khi make không cần thiết..."
    Language
Czech      -> Doc AnsiStyle
"Odstranění nepotřebných make závislostí..."
    Language
Korean     -> Doc AnsiStyle
"필요없는 make 의존성 제거 중..."
    Language
_          -> Doc AnsiStyle
"Removing unneeded make dependencies..."

----------------------------
-- Aura/Commands/B functions
----------------------------
-- NEEDS TRANSLATION
cleanStates_2 :: Int -> Language -> Doc AnsiStyle
cleanStates_2 :: Int -> Language -> Doc AnsiStyle
cleanStates_2 n :: Int
n@(Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle) -> (Int -> Text) -> Int -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Text
forall a. Show a => a -> Text
tshow -> Doc AnsiStyle
s) = \case
    Language
Japanese   -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"個のパッケージ状態記録だけが残される。その他削除?"
    Language
Arabic     -> Doc AnsiStyle
"سيتم الاحتفاظ بحالات الحزمة.هل تريد ازالة الباقي؟ " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s
    Language
Polish     -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" stan pakietów zostanie zachowany. Usunąć resztę?"
    Language
Croatian   -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" stanja paketa će biti zadržano. Ukloniti ostatak?"
    Language
German     -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" Paketzustände werden behalten. Den Rest entfernen?"
    Language
Spanish    -> Doc AnsiStyle
"El estado del paquete" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" se mantendrá. ¿Deseas eliminar el resto?"
    Language
Serbian    -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" стања пакета ће бити сачувано. Уклонити остатак?"
    Language
Norwegian  -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" pakketilstander vil bli beholdt. Vil du fjerne resten?"
    Language
Italian    -> Doc AnsiStyle
"Lo stato del pacchetto" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" sarà mantenuto. Rimuovere il resto?"
    Language
Portuguese -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" estados de pacotes serão mantidos. Remover o resto?"
    Language
French     -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" états des paquets vont être conservés. Supprimer le reste ?"
    Language
Russian    -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
-> Doc AnsiStyle -> Doc AnsiStyle -> Int -> Doc AnsiStyle
forall n a. Integral n => a -> a -> a -> n -> a
pluralRussian Doc AnsiStyle
" состояние пакетов будет оставлено." Doc AnsiStyle
" состояния пакетов будут оставлены." Doc AnsiStyle
" состояний пакетов будет оставлено." Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" Удалить оставшиеся?"
    Language
Indonesia  -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" paket akan tetap sama. Hapus yang lainnya?"
    Language
Chinese    -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" 个包的状态将会保留。删除其它的?"
    Language
Swedish    -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" paket kommer att bevaras. Ta bort resten?"
    Language
Esperanto  -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" statoj de pakaĵoj teniĝas. Ĉu forigi la ceteron?"
    Language
Dutch      -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" pakketstatussen worden behouden. Wilt u de rest verwijderen?"
    Language
Ukrainian  -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" стан пакунків будуть залишені. Видалити решту?"
    Language
Romanian   -> Doc AnsiStyle
"Stările pachetului " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" vor fi păstrate. Să se șteargă restul?"
    Language
Vietnamese -> Doc AnsiStyle
"Trạng thái của gói " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" sẽ được lưu lại. Loại bỏ phần còn lại?"
    Language
Czech      -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" stavy balíčků budou zachovány. Odstranit zbytek?"
    Language
Korean     -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" 패키지는 유지됩니다. 나머지를 제거하시겠습니까?"
    Language
_          -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" package states will be kept. Remove the rest?"

-- NEEDS TRANSLATION
cleanStates_3 :: Language -> Doc AnsiStyle
cleanStates_3 :: Language -> Doc AnsiStyle
cleanStates_3 = \case
    Language
Japanese   -> Doc AnsiStyle
"何も削除しないで終了します。"
    Language
Arabic     -> Doc AnsiStyle
".لم يتم ازالة اي حالة حزمة"
    Language
Polish     -> Doc AnsiStyle
"Żaden stan pakietu nie został usunięty."
    Language
Croatian   -> Doc AnsiStyle
"Nijedno stanje paketa nije uklonjeno."
    Language
German     -> Doc AnsiStyle
"Keine Paketzustände wurden entfernt."
    Language
Spanish    -> Doc AnsiStyle
"No se han eliminado estados de los paquetes."
    Language
Serbian    -> Doc AnsiStyle
"Ниједно стање пакета није уклоњено."
    Language
Norwegian  -> Doc AnsiStyle
"Ingen pakketilstander ble fjernet."
    Language
Italian    -> Doc AnsiStyle
"Nessuno stato dei pacchetti è stato rimosso."
    Language
Portuguese -> Doc AnsiStyle
"Nenhum estado de pacote será removido."
    Language
French     -> Doc AnsiStyle
"Aucun état des paquets n'a été supprimé."
    Language
Russian    -> Doc AnsiStyle
"Состояния пакетов отались нетронутыми."
    Language
Indonesia  -> Doc AnsiStyle
"Tidak ada paket yang dihapus."
    Language
Chinese    -> Doc AnsiStyle
"没有删除任何包。"
    Language
Swedish    -> Doc AnsiStyle
"Inga paket togs bort."
    Language
Esperanto  -> Doc AnsiStyle
"Ne statojn de pakaĵoj forigis."
    Language
Dutch      -> Doc AnsiStyle
"Er zijn geen pakketstatussen verwijderd."
    Language
Ukrainian  -> Doc AnsiStyle
"Стани пакунків залишились недоторкані."
    Language
Romanian   -> Doc AnsiStyle
"Nici o stare de pachet a fost ștearsă."
    Language
Vietnamese -> Doc AnsiStyle
"Không có trạng thái gói nào được lưu."
    Language
Czech      -> Doc AnsiStyle
"Nebyly odstraněny žádné stavy balíčku."
    Language
Korean     -> Doc AnsiStyle
"아무 패키지도 삭제되지 않았습니다."
    Language
_          -> Doc AnsiStyle
"No package states were removed."

cleanStates_4 :: Int -> Language -> Doc AnsiStyle
cleanStates_4 :: Int -> Language -> Doc AnsiStyle
cleanStates_4 Int
n = \case
  Language
Japanese  -> Doc AnsiStyle
"現在のパッケージ状態記録:" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"個。"
  Language
Arabic    -> Doc AnsiStyle
".محفوظة " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
" لديك حاليا حالات حزمة"
  Language
Polish    -> Doc AnsiStyle
"Chwilowo posiadasz" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"zapisanych stanów pakietów."
  Language
Spanish   -> Doc AnsiStyle
"Actualmente tiene " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"estados de paquetes guardados."
  Language
Russian   -> Doc AnsiStyle
"У вас сейчас " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
-> Doc AnsiStyle -> Doc AnsiStyle -> Int -> Doc AnsiStyle
forall n a. Integral n => a -> a -> a -> n -> a
pluralRussian Doc AnsiStyle
" сохраненное состояние пакета" Doc AnsiStyle
" сохраненных состояний пакета" Doc AnsiStyle
" сохраненных состояний пакетов." Int
n
  Language
Italian   -> Doc AnsiStyle
"Al momento ci sono" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"stati di pacchetti salvati."
  Language
Esperanto -> Doc AnsiStyle
"Vi havas " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
" konservajn statojn de pakaĵoj."
  Language
Dutch     -> Doc AnsiStyle
"U heeft momenteel" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"opgeslagen pakketstatussen."
  Language
Ukrainian -> Doc AnsiStyle
"Зараз ви маєте " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
" збережених станів пакунків."
  Language
Romanian  -> Doc AnsiStyle
"Momentan aveți " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
" stări de pachet salvate."
  Language
Vietnamese -> Doc AnsiStyle
"Bạn hiện đã lưu " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
" trạng thái gói."
  Language
Czech     -> Doc AnsiStyle
"V současné době máte " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
" uložených stavů balíčků."
  Language
Korean    -> Doc AnsiStyle
"현재" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"개의 패키지 상태가 저장되어 있습니다."
  Language
_         -> Doc AnsiStyle
"You currently have " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
" saved package states."

cleanStates_5 :: Text -> Language -> Doc AnsiStyle
cleanStates_5 :: Text -> Language -> Doc AnsiStyle
cleanStates_5 Text
t = \case
  Language
Japanese   -> Doc AnsiStyle
"一番最近に保存されたのは:" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t
  Language
Arabic     -> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
":احدث ما تم حفظه"
  Language
Polish     -> Doc AnsiStyle
"Ostatnio zapisane:" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t
  Language
Spanish    -> Doc AnsiStyle
"Guardado recientemente:" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t
  Language
Russian    -> Doc AnsiStyle
"Последнее сохраненное:" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t
  Language
Italian    -> Doc AnsiStyle
"Salvato più recentemente:" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t
  Language
Esperanto  -> Doc AnsiStyle
"Lastaj konservaj:" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t
  Language
Dutch      -> Doc AnsiStyle
"Onlangs opgeslagen:" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t
  Language
Ukrainian  -> Doc AnsiStyle
"Останні збереженні:" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t
  Language
Romanian   -> Doc AnsiStyle
"Cel mai recent salvat:" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t
  Language
Vietnamese -> Doc AnsiStyle
"Lần lưu gần nhất:" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t
  Language
Czech      -> Doc AnsiStyle
"Naposledy uložené:" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t
  Language
Korean     -> Doc AnsiStyle
"최근에 저장된 패키지:" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t
  Language
_          -> Doc AnsiStyle
"Most recently saved:" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t

cleanStates_6 :: Int -> Language -> Doc AnsiStyle
cleanStates_6 :: Int -> Language -> Doc AnsiStyle
cleanStates_6 Int
n = \case
  Language
Polish    -> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"jest przypiętych i nie zostanie usuniętych."
  Language
Arabic    -> Doc AnsiStyle
".اذا كانو مثبتين ولا يمكن ازالتهم " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n
  Language
Spanish   -> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"de estos están anclados y no se eliminarán."
  Language
Italian   -> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"di questi sono stati fissati, perciò non saranno rimossi."
  Language
Dutch     -> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"hiervan zijn vastgezet en worden daarom niet verwijderd."
  Language
Ukrainian -> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"були закріплені та залишуться недоторканими."
  Language
Romanian  -> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"dintre astea sunt fixate, și nu vor fi șterse."
  Language
Vietnamese -> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"trong số chúng đã được ghim, và sẽ không bị loại bỏ."
  Language
Czech     -> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"z nich jsou připnuté a nebudou odstraněny."
  Language
Korean    -> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"은(는) 고정되어 삭제되지 않습니다."
  Language
_         -> Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"of these are pinned, and won't be removed."

readState_1 :: Language -> Doc AnsiStyle
readState_1 :: Language -> Doc AnsiStyle
readState_1 = \case
    Language
Polish     -> Doc AnsiStyle
"Ten plik stanu nie mógł zostać odczytany. Czy jest to prawidłowy plik JSON?"
    Language
Arabic     -> Doc AnsiStyle
"صحيح؟ JSON فشل في تحليل ملف الحالة. هل"
    Language
Spanish    -> Doc AnsiStyle
"Ese archivo de estado no se pudo analizar. ¿Es un archivo JSON válido?"
    Language
Portuguese -> Doc AnsiStyle
"O arquivo de estado não pôde ser interpretado. É um arquivo JSON válido?"
    Language
Russian    -> Doc AnsiStyle
"Это состояние не распознано. Это корректный JSON?"
    Language
Italian    -> Doc AnsiStyle
"Non è stato possibile analizzare il file di stato. E' correttamente formattato in JSON?"
    Language
Esperanto  -> Doc AnsiStyle
"Tiu statdosiero paneis sintake analizi. Ĉu ĝi estas valida JSON?"
    Language
Dutch      -> Doc AnsiStyle
"Dit statusbestand kan niet worden verwerkt. Bevat het bestand geldige JSON?"
    Language
Ukrainian  -> Doc AnsiStyle
"Стан не був розпізнаний правильно. Це точно коректний JSON?"
    Language
Romanian   -> Doc AnsiStyle
"Acel fișier de stare nu se putea analiza. Este un fișier JSON valabil?"
    Language
Vietnamese -> Doc AnsiStyle
"Thất bại trong việc lấy dữ liệu từ tệp. Đó có đúng là tệp JSON?"
    Language
Czech      -> Doc AnsiStyle
"Tento stavový soubor se nepodařilo analyzovat. Je to legální JSON?"
    Language
Korean     -> Doc AnsiStyle
"상태 파일을 분석할 수 없습니다. 올바른 JSON 입니까?"
    Language
_          -> Doc AnsiStyle
"That state file failed to parse. Is it legal JSON?"

----------------------------
-- Aura/Commands/C functions
----------------------------
getDowngradeChoice_1 :: PkgName -> Language -> Doc AnsiStyle
getDowngradeChoice_1 :: PkgName -> Language -> Doc AnsiStyle
getDowngradeChoice_1 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle)
-> (PkgName -> Text) -> PkgName -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PkgName -> Text
pnName -> Doc AnsiStyle
p) = \case
    Language
Japanese   -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"はどのバージョンにしますか?"
    Language
Arabic     -> Doc AnsiStyle
"الذي تريده؟ . " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" ما هو اصدار"
    Language
Polish     -> Doc AnsiStyle
"Którą wersję pakietu " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" zainstalować?"
    Language
Croatian   -> Doc AnsiStyle
"Koju verziju paketa " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" želite?"
    Language
Swedish    -> Doc AnsiStyle
"Vilken version av " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" vill du ha?"
    Language
German     -> Doc AnsiStyle
"Welche Version von " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" möchten Sie haben?"
    Language
Spanish    -> Doc AnsiStyle
"¿Qué versión de " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" deseas?"
    Language
Portuguese -> Doc AnsiStyle
"Qual versão de " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" deseja?"
    Language
French     -> Doc AnsiStyle
"Quelle version de " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" voulez-vous ?"
    Language
Russian    -> Doc AnsiStyle
"Какую версию " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" вы хотите?"
    Language
Italian    -> Doc AnsiStyle
"Quale versione di " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" preferisci?"
    Language
Serbian    -> Doc AnsiStyle
"Коју верзију " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"-а желите?"
    Language
Norwegian  -> Doc AnsiStyle
"Hvilken versjon av " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" vil du ha?"
    Language
Indonesia  -> Doc AnsiStyle
"Versi dari paket " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" mana yang anda inginkan?"
    Language
Chinese    -> Doc AnsiStyle
"你希望安装 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" 的哪个版本?"
    Language
Esperanto  -> Doc AnsiStyle
"Kiu versio de " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" vi volas?"
    Language
Dutch      -> Doc AnsiStyle
"Welke versie van " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" wilt u?"
    Language
Ukrainian  -> Doc AnsiStyle
"Яку версію пакунку " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" ви бажаєте?"
    Language
Romanian   -> Doc AnsiStyle
"Care versiune al pachetului " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" o doriți?"
    Language
Vietnamese -> Doc AnsiStyle
"Bạn muốn sử dụng phiên bản nào của " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
    Language
Czech      -> Doc AnsiStyle
"Jakou verzi " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" chcete?"
    Language
Korean     -> Doc AnsiStyle
"어느 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" 버전을 설치하시겠습니까?"
    Language
_          -> Doc AnsiStyle
"What version of " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" do you want?"

backupCache_3 :: Language -> Doc AnsiStyle
backupCache_3 :: Language -> Doc AnsiStyle
backupCache_3 = \case
    Language
Japanese   -> Doc AnsiStyle
"バックアップ先は存在しません。"
    Language
Arabic     -> Doc AnsiStyle
".عدم وجود موقع النسخ الاحتياطي"
    Language
Polish     -> Doc AnsiStyle
"Lokalizacja kopii zapasowych nie istnieje."
    Language
Croatian   -> Doc AnsiStyle
"Lokacija sigurnosne kopije ne postoji."
    Language
Swedish    -> Doc AnsiStyle
"Specifierad backup-plats finns inte."
    Language
German     -> Doc AnsiStyle
"Der Sicherungsort existiert nicht."
    Language
Spanish    -> Doc AnsiStyle
"La localización para copia de seguridad no existe."
    Language
Portuguese -> Doc AnsiStyle
"Localização do backup não existe."
    Language
French     -> Doc AnsiStyle
"Le chemin des copies de sauvegarde spécifié n'existe pas."
    Language
Russian    -> Doc AnsiStyle
"Путь к бэкапу не существует."
    Language
Italian    -> Doc AnsiStyle
"La locazione di backup non esiste."
    Language
Serbian    -> Doc AnsiStyle
"Путања ка бекапу не постоји."
    Language
Norwegian  -> Doc AnsiStyle
"Spesifisert backup-plass finnes ikke."
    Language
Indonesia  -> Doc AnsiStyle
"Lokasi `backup` tidak ada."
    Language
Chinese    -> Doc AnsiStyle
"备份位置不存在。"
    Language
Esperanto  -> Doc AnsiStyle
"La savkopia loko ne ekzistas."
    Language
Dutch      -> Doc AnsiStyle
"De back-uplocatie bestaat niet."
    Language
Ukrainian  -> Doc AnsiStyle
"Шлях до резервної копії не існує."
    Language
Romanian   -> Doc AnsiStyle
"Locul de reservă nu există."
    Language
Vietnamese -> Doc AnsiStyle
"Đường dẫn sao lưu không tồn tại."
    Language
Czech      -> Doc AnsiStyle
"Umístění zálohy neexistuje."
    Language
Korean     -> Doc AnsiStyle
"백업 위치를 찾을 수 없습니다."
    Language
_          -> Doc AnsiStyle
"The backup location does not exist."

backupCache_4 :: FilePath -> Language -> Doc AnsiStyle
backupCache_4 :: String -> Language -> Doc AnsiStyle
backupCache_4 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle)
-> (String -> Text) -> String -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack -> Doc AnsiStyle
dir) = \case
    Language
Japanese   -> Doc AnsiStyle
"キャッシュのバックアップ先:" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
Arabic     -> Doc AnsiStyle
dir Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" التنسيخ الاحتياطي الى"
    Language
Polish     -> Doc AnsiStyle
"Tworzenie kopii zapasowej pamięci podręcznej w " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
Croatian   -> Doc AnsiStyle
"Stvaram sigurnosnu kopiju u " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
Swedish    -> Doc AnsiStyle
"Tar backup på cache-filer till " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
German     -> Doc AnsiStyle
"Sichere Cache in " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
Spanish    -> Doc AnsiStyle
"Haciendo una copia de seguridad de la caché en " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
Portuguese -> Doc AnsiStyle
"Backup do cache sendo feito em " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
French     -> Doc AnsiStyle
"Copie de sauvegarde dans " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"."
    Language
Russian    -> Doc AnsiStyle
"Бэкап создается в директории " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
Italian    -> Doc AnsiStyle
"Eseguo un backup della cache in " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
Serbian    -> Doc AnsiStyle
"Бекапујем кеш у " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
Norwegian  -> Doc AnsiStyle
"Tar backup på cache til " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
Indonesia  -> Doc AnsiStyle
"Melakukan `backup` pada direktori " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
Chinese    -> Doc AnsiStyle
"正在将缓存备份到 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
Esperanto  -> Doc AnsiStyle
"Enarkivigas la kaŝdosieron al " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
Dutch      -> Doc AnsiStyle
"Bezig met back-uppen van cache aan naar " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
Ukrainian  -> Doc AnsiStyle
"Зберігаємо резервну копію до " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
Romanian   -> Doc AnsiStyle
"Se copiază cache-ul de rezervă către " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
Vietnamese -> Doc AnsiStyle
"Sao lưu cache vào " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
Czech      -> Doc AnsiStyle
"Zálohování mezipaměti do " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
Korean     -> Doc AnsiStyle
"캐시를 백업하는 중 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir
    Language
_          -> Doc AnsiStyle
"Backing up cache to " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
dir

backupCache_5 :: Int -> Language -> Doc AnsiStyle
backupCache_5 :: Int -> Language -> Doc AnsiStyle
backupCache_5 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle) -> (Int -> Text) -> Int -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Text
forall a. Show a => a -> Text
tshow -> Doc AnsiStyle
n) = \case
    Language
Japanese   -> Doc AnsiStyle
"パッケージのファイル数:" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
Arabic     -> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" :حزمة الملفات الى النسخ الاحتياطي"
    Language
Polish     -> Doc AnsiStyle
"Pliki będące częścią\xa0kopii zapasowej: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
Croatian   -> Doc AnsiStyle
"Datoteke koje su dio sigurnosne kopije: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
Swedish    -> Doc AnsiStyle
"Paket-filer att ta backup på: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
German     -> Doc AnsiStyle
"Zu sichernde Paketdateien: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
Spanish    -> Doc AnsiStyle
"Ficheros de paquetes de los que se hará copia de seguridad: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
Portuguese -> Doc AnsiStyle
"Arquivos de pacotes para backup: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
French     -> Doc AnsiStyle
"Copie de sauvegarde des fichiers de paquets suivants : " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
Russian    -> Doc AnsiStyle
"Файлы пакета для бэкапа: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
Italian    -> Doc AnsiStyle
"Archivi dei pacchetti per cui sarà eseguito un backup: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
Serbian    -> Doc AnsiStyle
"Датотеке за бекап: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
Norwegian  -> Doc AnsiStyle
"Pakker som blir tatt backup på: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
Indonesia  -> Doc AnsiStyle
"Jumlah paket yang di-`backup`: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
Chinese    -> Doc AnsiStyle
"将要备份的包文件:" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
Esperanto  -> Doc AnsiStyle
"La dosierojn de la pakaĵoj enarkivigi: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
Dutch      -> Doc AnsiStyle
"Te back-uppen pakketbestanden: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
Ukrainian  -> Doc AnsiStyle
"Файли пакунку для резервної копії: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
Romanian   -> Doc AnsiStyle
"Fișiere de pachet pentru copiare de rezervă: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
Vietnamese -> Doc AnsiStyle
"Các tệp của gói sẽ được sao lưu: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
Czech      -> Doc AnsiStyle
"Soubory k zálohování: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
Korean     -> Doc AnsiStyle
"백업할 패키지 파일: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n
    Language
_          -> Doc AnsiStyle
"Package files to backup: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n

backupCache_6 :: Language -> Doc AnsiStyle
backupCache_6 :: Language -> Doc AnsiStyle
backupCache_6 = \case
    Language
Japanese   -> Doc AnsiStyle
"バックアップを実行しますか?"
    Language
Arabic     -> Doc AnsiStyle
"هل تريد ان تكمل النسخ الاحتياطي؟"
    Language
Polish     -> Doc AnsiStyle
"Kontynuować tworzenie kopii zapasowej?"
    Language
Croatian   -> Doc AnsiStyle
"Nastavi sa stvaranjem sigurnosne kopije?"
    Language
Swedish    -> Doc AnsiStyle
"Fortsätt med backup?"
    Language
German     -> Doc AnsiStyle
"Sicherung fortsetzen?"
    Language
Spanish    -> Doc AnsiStyle
"¿Proceder con la copia de seguridad?"
    Language
Portuguese -> Doc AnsiStyle
"Proceder com o backup?"
    Language
French     -> Doc AnsiStyle
"Procéder à la copie de sauvegarde ?"
    Language
Russian    -> Doc AnsiStyle
"Продолжить создание бэкапа?"
    Language
Italian    -> Doc AnsiStyle
"Procedere con il backup?"
    Language
Serbian    -> Doc AnsiStyle
"Наставити бекаповање?"
    Language
Norwegian  -> Doc AnsiStyle
"Fortsett med backup?"
    Language
Indonesia  -> Doc AnsiStyle
"Lanjutkan dengan `backup`?"
    Language
Chinese    -> Doc AnsiStyle
"开始备份?"
    Language
Esperanto  -> Doc AnsiStyle
"Ĉu daŭrigu enarkivigi?"
    Language
Dutch      -> Doc AnsiStyle
"Wilt u doorgaan met back-uppen?"
    Language
Ukrainian  -> Doc AnsiStyle
"Продовжити створення резервної копії?"
    Language
Romanian   -> Doc AnsiStyle
"Continuați cu copiile de rezervă?"
    Language
Vietnamese -> Doc AnsiStyle
"Tiến hành sao lưu?"
    Language
Czech      -> Doc AnsiStyle
"Pokračovat v zálohování."
    Language
Korean     -> Doc AnsiStyle
"백업 하시겠습니까?"
    Language
_          -> Doc AnsiStyle
"Proceed with backup?"

backupCache_7 :: Language -> Doc AnsiStyle
backupCache_7 :: Language -> Doc AnsiStyle
backupCache_7 = \case
    Language
Japanese   -> Doc AnsiStyle
"バックアップは意図的に阻止されました。"
    Language
Arabic     -> Doc AnsiStyle
".اقاف النسخ الاحتياطي يدويا"
    Language
Polish     -> Doc AnsiStyle
"Tworzenie kopii zapasowej zostało przerwane przez użytkownika."
    Language
Croatian   -> Doc AnsiStyle
"Stvaranje sigurnosne kopije prekinuto od strane korisnika."
    Language
Swedish    -> Doc AnsiStyle
"Backup avbröts manuellt."
    Language
German     -> Doc AnsiStyle
"Backup durch Benutzer abgebrochen."
    Language
Spanish    -> Doc AnsiStyle
"Copia de seguridad abortada manualmente."
    Language
Portuguese -> Doc AnsiStyle
"Backup cancelado manualmente."
    Language
French     -> Doc AnsiStyle
"Copie de sauvegarde manuelle annulée."
    Language
Russian    -> Doc AnsiStyle
"Создание бэкапа прервано пользователем."
    Language
Italian    -> Doc AnsiStyle
"Backup interrotto manualmente."
    Language
Serbian    -> Doc AnsiStyle
"Бекаповање је ручно прекинуто."
    Language
Norwegian  -> Doc AnsiStyle
"Backup ble avbrutt manuelt."
    Language
Indonesia  -> Doc AnsiStyle
"Proses `backup` dibatalkan secara paksa."
    Language
Chinese    -> Doc AnsiStyle
"手动备份已中止。"
    Language
Esperanto  -> Doc AnsiStyle
"Enarkivigadon ĉesigis permane."
    Language
Dutch      -> Doc AnsiStyle
"Het back-upproces is handmatig afgebroken."
    Language
Ukrainian  -> Doc AnsiStyle
"Створення резервної копії перервано користувачем."
    Language
Romanian   -> Doc AnsiStyle
"Copiarea de rezervă anulată manual."
    Language
Vietnamese -> Doc AnsiStyle
"Quá trình sao lưu được hủy."
    Language
Czech      -> Doc AnsiStyle
"Zálohování ručně přerušeno."
    Language
Korean     -> Doc AnsiStyle
"백업이 중지되었습니다."
    Language
_          -> Doc AnsiStyle
"Backup manually aborted."

backupCache_8 :: Language -> Doc AnsiStyle
backupCache_8 :: Language -> Doc AnsiStyle
backupCache_8 = \case
    Language
Japanese   -> Doc AnsiStyle
"バックアップ中。数分かかるかもしれません。"
    Language
Arabic     -> Doc AnsiStyle
"...النسخ الاحتياطي. هذه العملية يمكن ان تاخذ وقت"
    Language
Polish     -> Doc AnsiStyle
"Tworzenie kopii zapasowej. To może potrwać kilka minut..."
    Language
Croatian   -> Doc AnsiStyle
"Stvaranje sigurnosne kopije. Ovo može potrajati nekoliko minuta..."
    Language
Swedish    -> Doc AnsiStyle
"Tar backup. Det här kan ta ett tag..."
    Language
German     -> Doc AnsiStyle
"Sichere. Dies kann einige Minuten dauern..."
    Language
Spanish    -> Doc AnsiStyle
"Haciendo copia de seguridad. Esto puede tardar unos minutos..."
    Language
Portuguese -> Doc AnsiStyle
"Efetuando backup. Isso pode levar alguns minutos..."
    Language
French     -> Doc AnsiStyle
"Copie de sauvegarde en cours. Ceci peut prendre quelques minutes…"
    Language
Russian    -> Doc AnsiStyle
"Создается бэкап. Это может занять пару минут..."
    Language
Italian    -> Doc AnsiStyle
"Esecuzione del backup in corso. Potrebbe volerci qualche minuto..."
    Language
Serbian    -> Doc AnsiStyle
"Бекапујем. Ово може да потраје пар минута..."
    Language
Norwegian  -> Doc AnsiStyle
"Tar backup. Dette kan ta en stund..."
    Language
Indonesia  -> Doc AnsiStyle
"Melakukan `backup`. Proses ini akan berjalan untuk beberapa menit..."
    Language
Chinese    -> Doc AnsiStyle
"正在备份中。可能需要几分钟的时间..."
    Language
Esperanto  -> Doc AnsiStyle
"Enarkiviganta. Ĉi tiu eble daŭros dum kelkaj tagoj..."
    Language
Dutch      -> Doc AnsiStyle
"Er wordt een back-up gemaakt. Dit kan enkele minuten duren…"
    Language
Ukrainian  -> Doc AnsiStyle
"Створюємо резервну копію. Це може зайняти декілька хвилин..."
    Language
Romanian   -> Doc AnsiStyle
"Se fac copii de rezervă. Ar putea să dureze câteva minute..."
    Language
Vietnamese -> Doc AnsiStyle
"Đang sao lưu. Có thể sẽ mất vài phút..."
    Language
Czech      -> Doc AnsiStyle
"Zálohování. Může to trvat několik minut..."
    Language
Korean     -> Doc AnsiStyle
"백업 중입니다. 몇 분 정도 걸릴 수 있습니다..."
    Language
_          -> Doc AnsiStyle
"Backing up. This may take a few minutes..."

copyAndNotify_1 :: Int -> Language -> Doc AnsiStyle
copyAndNotify_1 :: Int -> Language -> Doc AnsiStyle
copyAndNotify_1 (Doc AnsiStyle -> Doc AnsiStyle
cyan (Doc AnsiStyle -> Doc AnsiStyle)
-> (Int -> Doc AnsiStyle) -> Int -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty -> Doc AnsiStyle
n) = \case
    Language
Japanese   -> Doc AnsiStyle
"#[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]をコピー中・・・"
    Language
Arabic     -> Doc AnsiStyle
"["Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]# نسخ"
    Language
Polish     -> Doc AnsiStyle
"Kopiowanie #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
Turkish    -> Doc AnsiStyle
"Kopyalanıyor #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
Croatian   -> Doc AnsiStyle
"Kopiranje #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
Swedish    -> Doc AnsiStyle
"Kopierar #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
German     -> Doc AnsiStyle
"Kopiere #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
Spanish    -> Doc AnsiStyle
"Copiando #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
Portuguese -> Doc AnsiStyle
"Copiando #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
French     -> Doc AnsiStyle
"Copie de #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
Russian    -> Doc AnsiStyle
"Копируется #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
Italian    -> Doc AnsiStyle
"Copiando #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<>Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
Serbian    -> Doc AnsiStyle
"Копирам #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
Norwegian  -> Doc AnsiStyle
"Kopierer #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
Indonesia  -> Doc AnsiStyle
"Menyalin #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
Chinese    -> Doc AnsiStyle
"正在复制 #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
Esperanto  -> Doc AnsiStyle
"Kopianta #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
Dutch      -> Doc AnsiStyle
"Bezig met kopiëren: #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
Ukrainian  -> Doc AnsiStyle
"Копіюємо #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
Romanian   -> Doc AnsiStyle
"Se copiază #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
Vietnamese -> Doc AnsiStyle
"Sao chép #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
Czech      -> Doc AnsiStyle
"Kopírování #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
Korean     -> Doc AnsiStyle
"복사중 #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"
    Language
_          -> Doc AnsiStyle
"Copying #[" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"]"

cleanCache_2 :: Language -> Doc AnsiStyle
cleanCache_2 :: Language -> Doc AnsiStyle
cleanCache_2 = \case
    Language
Japanese   -> Doc AnsiStyle
"パッケージ・キャッシュは完全に削除されます。"
    Language
Arabic     -> Doc AnsiStyle
".هذا سوف يحذف ذاكرة التخزين الموقت للحزمة بالكامل"
    Language
Polish     -> Doc AnsiStyle
"To usunie WSZYSTKIE pakiety z pamięci podręcznej."
    Language
Croatian   -> Doc AnsiStyle
"Ovo će izbrisati CIJELI cache paketa."
    Language
Swedish    -> Doc AnsiStyle
"Detta kommer ta bort HELA paket-cachen."
    Language
German     -> Doc AnsiStyle
"Dies wird den GESAMTEN Paketcache leeren."
    Language
Spanish    -> Doc AnsiStyle
"Esto eliminará POR COMPLETO la caché de paquetes."
    Language
Portuguese -> Doc AnsiStyle
"Isso removerá TODOS OS PACOTES do cache."
    Language
French     -> Doc AnsiStyle
"Ceci va supprimer la TOTALITÉ du cache des paquets."
    Language
Russian    -> Doc AnsiStyle
"Это действие ВСЕЦЕЛО уничтожит кэш пакетов."
    Language
Italian    -> Doc AnsiStyle
"Questa operazione cancellerà l'INTERA cache dei pacchetti."
    Language
Serbian    -> Doc AnsiStyle
"Ово ће избрисати ЦЕО кеш пакета."
    Language
Norwegian  -> Doc AnsiStyle
"Dette vil slette HELE pakke-cachen."
    Language
Indonesia  -> Doc AnsiStyle
"Akan menghapus SEMUA `cache` paket"
    Language
Chinese    -> Doc AnsiStyle
"这将会删除全部的包缓存。"
    Language
Esperanto  -> Doc AnsiStyle
"Ĉi tiu forigos la TUTAN kaŝmemoron de pakaĵoj."
    Language
Dutch      -> Doc AnsiStyle
"Hiermee wordt de GEHELE pakketcache gewist."
    Language
Ukrainian  -> Doc AnsiStyle
"Ця операція ПОВНІСТЮ видалить кеш пакунків."
    Language
Romanian   -> Doc AnsiStyle
"Asta va șterge COMPLET cache-ul de pachete."
    Language
Vietnamese -> Doc AnsiStyle
"Điều này sẽ xóa TOÀN BỘ cache của gói."
    Language
Czech      -> Doc AnsiStyle
"Tím smažete CELOU mezipaměť balíčku."
    Language
Korean     -> Doc AnsiStyle
"모든 패키지 캐시가 삭제됩니다."
    Language
_          -> Doc AnsiStyle
"This will delete the ENTIRE package cache."

cleanCache_3 :: Word -> Language -> Doc AnsiStyle
cleanCache_3 :: Word -> Language -> Doc AnsiStyle
cleanCache_3 n :: Word
n@(Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle) -> (Word -> Text) -> Word -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> Text
forall a. Show a => a -> Text
tshow -> Doc AnsiStyle
s) = \case
    Language
Japanese   -> Doc AnsiStyle
"パッケージ・ファイルは" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"個保存されます。"
    Language
Arabic     -> Doc AnsiStyle
".من كل ملف حزمة سيتم الاحتفاظ بها " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s
    Language
Polish     -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" wersji każdego pakietu zostanie zachowane."
    Language
Croatian   -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" zadnjih verzija svakog paketa će biti zadržano."
    Language
Swedish    -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" av varje paketfil kommer att sparas."
    Language
German     -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" jeder Paketdatei wird behalten."
    Language
Spanish    -> Doc AnsiStyle
"Se mantendrán " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" ficheros de cada paquete."
    Language
Portuguese -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" arquivos de cada pacote serão mantidos."
    Language
French     -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" fichiers de chaque paquet sera conservé."
    Language
Russian    -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
-> Doc AnsiStyle -> Doc AnsiStyle -> Word -> Doc AnsiStyle
forall n a. Integral n => a -> a -> a -> n -> a
pluralRussian Doc AnsiStyle
" версия каждого пакета будет нетронута." Doc AnsiStyle
" версии каждого пакета будут нетронуты." Doc AnsiStyle
" версий каждого пакета будут нетронуты." Word
n
    Language
Italian    -> Doc AnsiStyle
"Saranno mantenuti " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" file di ciascun pacchetto."
    Language
Serbian    -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" верзије сваког од пакета ће бити сачуване."
    Language
Norwegian  -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" av hver pakkefil blir beholdt."
    Language
Indonesia  -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" berkas dari tiap paket akan disimpan."
    Language
Chinese    -> Doc AnsiStyle
"每个包文件将会保存 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" 个版本。"
    Language
Esperanto  -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" de ĉiu dosiero de pakaĵo teniĝos."
    Language
Dutch      -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" van elk pakketbestand wordt bewaard."
    Language
Ukrainian  -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" версія кожного пакунку залишиться недоторканою."
    Language
Romanian   -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" din fiecare fișier de pachet vor fi păstrate."
    Language
Vietnamese -> Doc AnsiStyle
"Sẽ giữ lại " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" tệp của gói."
    Language
Czech      -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" každého souboru balíčku bude zachován."
    Language
Korean     -> Doc AnsiStyle
"각 패키지 파일에 대해 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"개의 파일이 유지되어야 합니다."
    Language
_          -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" of each package file will be kept."

cleanCache_4 :: Language -> Doc AnsiStyle
cleanCache_4 :: Language -> Doc AnsiStyle
cleanCache_4 = \case
    Language
Japanese   -> Doc AnsiStyle
"残りは全部削除されます。承知していますか?"
    Language
Arabic     -> Doc AnsiStyle
"سيتم حذف الباقي. هل تريد أن تكمل؟"
    Language
Polish     -> Doc AnsiStyle
"Wszystko inne zostanie usunięte. Na pewno?"
    Language
Croatian   -> Doc AnsiStyle
"Ostali paketi će biti izbrisani. Jeste li sigurni?"
    Language
Swedish    -> Doc AnsiStyle
"Resten kommer att tas bort. Är det OK?"
    Language
German     -> Doc AnsiStyle
"Der Rest wird gelöscht. Ist das OK?"
    Language
Spanish    -> Doc AnsiStyle
"El resto se eliminarán. ¿De acuerdo?"
    Language
Portuguese -> Doc AnsiStyle
"O resto será removido. OK?"
    Language
French     -> Doc AnsiStyle
"Le reste sera supprimé. Êtes-vous d'accord ?"
    Language
Russian    -> Doc AnsiStyle
"Всё остальное будет удалено. Годится?"
    Language
Italian    -> Doc AnsiStyle
"Il resto sarà rimosso. Continuare?"
    Language
Serbian    -> Doc AnsiStyle
"Остатак ће бити избрисан. Да ли је то у реду?"
    Language
Norwegian  -> Doc AnsiStyle
"Resten vil bli slettet. Er det OK?"
    Language
Indonesia  -> Doc AnsiStyle
"Selainnya akan dihapus. Ikhlas kan?"
    Language
Chinese    -> Doc AnsiStyle
"其余的将会被删除。确定?"
    Language
Esperanto  -> Doc AnsiStyle
"La cetero foriĝos. Ĉu bone?"
    Language
Dutch      -> Doc AnsiStyle
"De rest wordt gewist. Weet u het zeker?"
    Language
Ukrainian  -> Doc AnsiStyle
"Все інше буде видалено. Гаразд?"
    Language
Romanian   -> Doc AnsiStyle
"Restul va fi șters. De acord?"
    Language
Vietnamese -> Doc AnsiStyle
"Xóa bỏ phần còn lại. Ok?"
    Language
Czech      -> Doc AnsiStyle
"Zbytek bude smazán. Ok?"
    Language
Korean     -> Doc AnsiStyle
"나머지는 모두 삭제됩니다. 계속하시겠습니까?"
    Language
_          -> Doc AnsiStyle
"The rest will be deleted. Okay?"

cleanCache_5 :: Language -> Doc AnsiStyle
cleanCache_5 :: Language -> Doc AnsiStyle
cleanCache_5 = \case
    Language
Japanese   -> Doc AnsiStyle
"削除の続行は意図的に阻止されました。"
    Language
Arabic     -> Doc AnsiStyle
".تم ايقاف تنظيف ذاكرة الموقت يدويا"
    Language
Polish     -> Doc AnsiStyle
"Czyszczenie pamięci podręcznej zostało przerwane przez użytkownika."
    Language
Croatian   -> Doc AnsiStyle
"Čišćenje cache-a paketa prekinuto od strane korisnika."
    Language
Swedish    -> Doc AnsiStyle
"Cache-rensning avbröts manuellt."
    Language
German     -> Doc AnsiStyle
"Leeren des Caches durch Benutzer abgebrochen."
    Language
Spanish    -> Doc AnsiStyle
"Limpieza de la caché abortada manualmente."
    Language
Portuguese -> Doc AnsiStyle
"Limpeza do cache cancelada manualmente."
    Language
French     -> Doc AnsiStyle
"Le nettoyage du cache a été arrêté manuellement."
    Language
Russian    -> Doc AnsiStyle
"Очистка кэша прервана пользователем."
    Language
Italian    -> Doc AnsiStyle
"La pulizia della cache è stata interrotta manualmente."
    Language
Serbian    -> Doc AnsiStyle
"Чишћење кеша је ручно прекинуто."
    Language
Norwegian  -> Doc AnsiStyle
"Cache-rensing ble avbrutt manuelt."
    Language
Indonesia  -> Doc AnsiStyle
"Pembersihan `cache` dibatalkan secara paksa."
    Language
Chinese    -> Doc AnsiStyle
"手动清理缓存已中止。"
    Language
Esperanto  -> Doc AnsiStyle
"Puriganta Kaŝmemoro ĉesis permane."
    Language
Dutch      -> Doc AnsiStyle
"De cache-opruiming is handmatig afgebroken."
    Language
Ukrainian  -> Doc AnsiStyle
"Очищення кешу було перервано користувачем."
    Language
Romanian   -> Doc AnsiStyle
"Curățenia cache-ului anulată manual."
    Language
Vietnamese -> Doc AnsiStyle
"Đã hủy xóa cache."
    Language
Czech      -> Doc AnsiStyle
"Čištění mezipaměti bylo ručně přerušeno"
    Language
Korean     -> Doc AnsiStyle
"캐시 정리가 중지되었습니다."
    Language
_          -> Doc AnsiStyle
"Cache cleaning manually aborted."

cleanCache_6 :: Language -> Doc AnsiStyle
cleanCache_6 :: Language -> Doc AnsiStyle
cleanCache_6 = \case
    Language
Japanese   -> Doc AnsiStyle
"パッケージ・キャッシュを掃除中・・・"
    Language
Arabic     -> Doc AnsiStyle
"...تنظيف رزمة الذاكرة التخزين الموقت"
    Language
Polish     -> Doc AnsiStyle
"Czyszczenie pamięci podręcznej..."
    Language
Croatian   -> Doc AnsiStyle
"Čišćenje cache-a paketa..."
    Language
Swedish    -> Doc AnsiStyle
"Rensar paket-cache..."
    Language
German     -> Doc AnsiStyle
"Leere Paketcache..."
    Language
Spanish    -> Doc AnsiStyle
"Limpiando la caché de paquetes..."
    Language
Portuguese -> Doc AnsiStyle
"Limpando cache de pacotes..."
    Language
French     -> Doc AnsiStyle
"Nettoyage du cache des paquets…"
    Language
Russian    -> Doc AnsiStyle
"Очистка кэша пакета..."
    Language
Italian    -> Doc AnsiStyle
"Pulizia della cache dei pacchetti..."
    Language
Serbian    -> Doc AnsiStyle
"Чишћење кеша..."
    Language
Norwegian  -> Doc AnsiStyle
"Renser pakke-cache..."
    Language
Indonesia  -> Doc AnsiStyle
"Membersihkan `cache` paket..."
    Language
Chinese    -> Doc AnsiStyle
"正在清理包缓存..."
    Language
Esperanto  -> Doc AnsiStyle
"Purigas Kaŝmemoron de pakaĵoj..."
    Language
Dutch      -> Doc AnsiStyle
"Bezig met opruimen van pakketcache…"
    Language
Ukrainian  -> Doc AnsiStyle
"Очищуємо кеш пакунків..."
    Language
Romanian   -> Doc AnsiStyle
"Se curăță cache-ul de pachete..."
    Language
Vietnamese -> Doc AnsiStyle
"Xóa cache..."
    Language
Czech      -> Doc AnsiStyle
"Čištění mezipaměti balíčků"
    Language
Korean     -> Doc AnsiStyle
"패키지 캐시 정리 중..."
    Language
_          -> Doc AnsiStyle
"Cleaning package cache..."

cleanCache_7 :: Word -> Word -> Language -> Doc AnsiStyle
cleanCache_7 :: Word -> Word -> Language -> Doc AnsiStyle
cleanCache_7 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle) -> (Word -> Text) -> Word -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> Text
forall a. Show a => a -> Text
tshow -> Doc AnsiStyle
ps) (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle) -> (Word -> Text) -> Word -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> Text
forall a. Show a => a -> Text
tshow -> Doc AnsiStyle
bytes) = \case
    Language
Arabic     -> Doc AnsiStyle
".ميغابايت " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
bytes Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" الذي تاخذ " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
ps Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" الذاكرة التخزين الموقت فيه الرزمة"
    Language
Polish     -> Doc AnsiStyle
"Pamięć podręczna posiada " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
ps Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" pakietów, zajmujących " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
bytes Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" megabajtów."
    Language
Spanish    -> Doc AnsiStyle
"La caché contiene " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
ps Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" paquetes, consumiendo " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
bytes Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" megabytes."
    Language
Ukrainian  -> Doc AnsiStyle
"Кеш містить " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
ps Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" пакунків, які використовують " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
bytes Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" МБ місця."
    Language
Romanian   -> Doc AnsiStyle
"Cache-ul conține " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
ps Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" pachete, consumând " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
bytes Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" MB."
    Language
Vietnamese -> Doc AnsiStyle
"Có " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
ps Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" gói trong cache, chiếm " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
bytes Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" megabytes."
    Language
Korean     -> Doc AnsiStyle
ps Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"개의 패키지는 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
bytes Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"MB 사용 중입니다."
    Language
Dutch      -> Doc AnsiStyle
"De cache bevat " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
ps Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" pakketten, met een totale omvang van " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
bytes Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" megabytes."
    Language
_          -> Doc AnsiStyle
"The cache contains " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
ps Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" packages, consuming " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
bytes Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" megabytes."

cleanCache_8 :: Word -> Language -> Doc AnsiStyle
cleanCache_8 :: Word -> Language -> Doc AnsiStyle
cleanCache_8 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle) -> (Word -> Text) -> Word -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> Text
forall a. Show a => a -> Text
tshow -> Doc AnsiStyle
bytes) = \case
    Language
Arabic     -> Doc AnsiStyle
".ميغابايت محررة " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
bytes
    Language
Polish     -> Doc AnsiStyle
bytes Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" megabajtów zwolnionych."
    Language
Spanish    -> Doc AnsiStyle
bytes Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" megabytes liberados."
    Language
Ukrainian  -> Doc AnsiStyle
bytes Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" МБ звільнилось."
    Language
Romanian   -> Doc AnsiStyle
bytes Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" MB eliberat."
    Language
Vietnamese -> Doc AnsiStyle
"Giải phóng " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
bytes Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"megabytes."
    Language
Czech      -> Doc AnsiStyle
"Uvolněno " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
bytes Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" MB."
    Language
Korean     -> Doc AnsiStyle
bytes Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" MB 정리되었습니다."
    Language
Dutch      -> Doc AnsiStyle
bytes Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"megabytes vrijgemaakt."
    Language
_          -> Doc AnsiStyle
bytes Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" megabytes freed."

cleanCache_9 :: Word -> Language -> Doc AnsiStyle
cleanCache_9 :: Word -> Language -> Doc AnsiStyle
cleanCache_9 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle) -> (Word -> Text) -> Word -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> Text
forall a. Show a => a -> Text
tshow -> Doc AnsiStyle
w) = \case
    Language
Romanian   -> Doc AnsiStyle
w Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" versiuni din fiecare pachet instalat vor fi păstrate."
    Language
Vietnamese -> Doc AnsiStyle
"Sẽ giữ lại " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
w Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" phiên bản của các gói đã cài đặt."
    Language
Czech      -> Doc AnsiStyle
w Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" verze každého nainstalovaného balíčku budou zachovány."
    Language
Korean     -> Doc AnsiStyle
"각각의 설치된 패키지의 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
w Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"은(는) 유지됩니다."
    Language
Dutch      -> Doc AnsiStyle
"Er worden " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
w Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"versies van elke geïnstalleerd pakket bewaard."
    Language
_          -> Doc AnsiStyle
w Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" versions of each installed package will be kept."

-- NEEDS TRANSLATION
cleanNotSaved_1 :: Language -> Doc AnsiStyle
cleanNotSaved_1 :: Language -> Doc AnsiStyle
cleanNotSaved_1 = \case
    Language
Japanese   -> Doc AnsiStyle
"不要パッケージファイルを確認・・・"
    Language
Arabic     -> Doc AnsiStyle
"...تحديد ملفات الحزم غير الضرورية"
    Language
Polish     -> Doc AnsiStyle
"Określanie niepotrzebnych plików pakietów..."
    Language
Croatian   -> Doc AnsiStyle
"Pronalazim nepotrebne datoteke paketa..."
    Language
German     -> Doc AnsiStyle
"Bestimme nicht benötigte Paketdateien..."
    Language
Spanish    -> Doc AnsiStyle
"Determinando ficheros de paquetes innecesarios..."
    Language
Norwegian  -> Doc AnsiStyle
"Finner unødige pakkefiler..."
    Language
Italian    -> Doc AnsiStyle
"Inviduazione dei pacchetti non più necessari..."
    Language
Portuguese -> Doc AnsiStyle
"Determinando pacotes não necessários..."
    Language
French     -> Doc AnsiStyle
"Détermination des fichiers de paquet inutiles…"
    Language
Russian    -> Doc AnsiStyle
"Вычисляются ненужные файлы пакетов..."
    Language
Indonesia  -> Doc AnsiStyle
"Menentukan berkas paket yang tidak dibutuhkan..."
    Language
Chinese    -> Doc AnsiStyle
"正在确定不需要的包文件..."
    Language
Swedish    -> Doc AnsiStyle
"Beräknar onödiga paketfiler..."
    Language
Esperanto  -> Doc AnsiStyle
"Decidas nebezonajn dosierojn de pakaĵoj..."
    Language
Dutch      -> Doc AnsiStyle
"Bezig met vaststellen van overbodige pakketbestanden…"
    Language
Ukrainian  -> Doc AnsiStyle
"Визначачення непотрібних пакунків..."
    Language
Romanian   -> Doc AnsiStyle
"Se determin fișiere de pachet inutile..."
    Language
Vietnamese -> Doc AnsiStyle
"Xác định các tệp của gói không cần thiết..."
    Language
Czech      -> Doc AnsiStyle
"Zjišťování nepotřebných souborů balíčků..."
    Language
Korean     -> Doc AnsiStyle
"필요 없는 패키지 파일 확인 중..."
    Language
_          -> Doc AnsiStyle
"Determining unneeded package files..."

-- NEEDS TRANSLATION
cleanNotSaved_2 :: Int -> Language -> Doc AnsiStyle
cleanNotSaved_2 :: Int -> Language -> Doc AnsiStyle
cleanNotSaved_2 n :: Int
n@(Doc AnsiStyle -> Doc AnsiStyle
cyan (Doc AnsiStyle -> Doc AnsiStyle)
-> (Int -> Doc AnsiStyle) -> Int -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty -> Doc AnsiStyle
s) = \case
    Language
Japanese   -> Doc AnsiStyle
"「" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"」の不要パッケージファイルがあります。削除しますか?"
    Language
Arabic     -> Doc AnsiStyle
"تم العثور على ملفات الحزمة غير الضرورية.هل تريد حذفه؟ " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s
    Language
Polish     -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" niepotrzebnych plików zostało znalezionych. Usunąć?"
    Language
Croatian   -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" nepotrebnih datoteka pronađeno. Obrisati?"
    Language
German     -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" nicht benötigte Paketdateien gefunden. Löschen?"
    Language
Spanish    -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" ficheros innecesarios de paquetes encontrados. ¿Deseas eliminarlos?"
    Language
Norwegian  -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" unødige pakkefiler funnet. Vil du slette?"
    Language
Italian    -> Doc AnsiStyle
"Sono stati trovati " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" file non necessari per i pacchetti. Cancellarli?"
    Language
Portuguese -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" pacotes não necessários encontrados. Removê-los?"
    Language
French     -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" paquets inutiles trouvés. Les supprimer ?"
    Language
Russian    -> Doc AnsiStyle
-> Doc AnsiStyle -> Doc AnsiStyle -> Int -> Doc AnsiStyle
forall n a. Integral n => a -> a -> a -> n -> a
pluralRussian (Doc AnsiStyle
"Обнаружен " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" ненужный файл пакета.") (Doc AnsiStyle
"Обнаружены " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" ненужных файла пакетов.") (Doc AnsiStyle
"Обнаружено " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" ненужных файлов пакетов.") Int
n Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" Удалить?"
    Language
Indonesia  -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" berkas paket yang tidak dibutuhkan ditemukan. Hapus?"
    Language
Chinese    -> Doc AnsiStyle
"发现了 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" 个不需要的包文件。是否删除?"
    Language
Swedish    -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" oanvända paket hittades. Ta bort?"
    Language
Esperanto  -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" nebezonajn dosierojn de pakaĵoj trovis. Ĉu forigi"
    Language
Dutch      -> Doc AnsiStyle
"Er zijn " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" overbodige pakketbestanden aangetroffen. Wilt u deze bestanden wissen?"
    Language
Ukrainian  -> Doc AnsiStyle
"Знайдено " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" непотрібних пакунків. Видалити?"
    Language
Romanian   -> Doc AnsiStyle
"S-au găsit " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" fișiere de pachet inutile. Ștergeți?"
    Language
Vietnamese -> Doc AnsiStyle
"Tìm thấy " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" gói không cần thiết. Xóa bỏ?"
    Language
Czech      -> Doc AnsiStyle
"Nepotřebné soubory balíčků: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
". Vymazat?"
    Language
Korean     -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"는 필요 없는 패키지 파일입니다. 삭제하시겠습니까?"
    Language
_          -> Doc AnsiStyle
s Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" unneeded package files found. Delete?"

----------------------------
-- Aura/Commands/L functions
----------------------------
logLookUpFields :: Language -> [Text]
logLookUpFields :: Language -> [Text]
logLookUpFields = [Language -> Text] -> Language -> [Text]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [ Language -> Text
Fields.package
                           , Language -> Text
Fields.firstInstall
                           , Language -> Text
Fields.upgrades
                           , Language -> Text
Fields.recentActions ]

reportNotInLog_1 :: Language -> Doc AnsiStyle
reportNotInLog_1 :: Language -> Doc AnsiStyle
reportNotInLog_1 = \case
    Language
Japanese   -> Doc AnsiStyle
"logファイルには出ていない:"
    Language
Arabic     -> Doc AnsiStyle
":لم تظهر هذه في ملف السجل"
    Language
Polish     -> Doc AnsiStyle
"Tych pakietów nie ma w dzienniku:"
    Language
Croatian   -> Doc AnsiStyle
"Ovih paketa nema u dnevniku:"
    Language
Swedish    -> Doc AnsiStyle
"Dessa har inte framkommit i loggfiler:"
    Language
German     -> Doc AnsiStyle
"Diese sind nicht in der Logdatei aufgetaucht:"
    Language
Spanish    -> Doc AnsiStyle
"Estos no aparecen en el fichero log:"
    Language
Portuguese -> Doc AnsiStyle
"Os seguintes não apareceram no arquivo de log:"
    Language
French     -> Doc AnsiStyle
"Ceci n'apparaît pas des les journaux (log) :"
    Language
Russian    -> Doc AnsiStyle
"Следующих пакетов нет в лог-файле:"
    Language
Italian    -> Doc AnsiStyle
"Questi non sono apparsi nel file di log:"
    Language
Serbian    -> Doc AnsiStyle
"Ови пакети се не спомињу у дневнику:"
    Language
Norwegian  -> Doc AnsiStyle
"Følgende har ikke vist seg i loggen:"
    Language
Indonesia  -> Doc AnsiStyle
"Tidak terlihat pada berkas log:"
    Language
Chinese    -> Doc AnsiStyle
"这些没有在日志文件中出现:"
    Language
Esperanto  -> Doc AnsiStyle
"Ĉi tiuj ne enestis la protokolajn dosierojn:"
    Language
Dutch      -> Doc AnsiStyle
"Deze zijn niet toegevoegd aan het logboek:"
    Language
Ukrainian  -> Doc AnsiStyle
"Наступних пакунків немає в лог файлі:"
    Language
Romanian   -> Doc AnsiStyle
"Acestea nu au apărut în log:"
    Language
Vietnamese -> Doc AnsiStyle
"Nội dung sau không có trong tệp log:"
    Language
Czech      -> Doc AnsiStyle
"Tyto se neobjevily v souboru log:"
    Language
Korean     -> Doc AnsiStyle
"로그 파일에 나타나지 않음:"
    Language
_          -> Doc AnsiStyle
"These have not appeared in the log file:"

-------------------------------
-- Aura/AUR functions
-------------------------------

packageNotFound_1 :: Language -> Doc AnsiStyle
packageNotFound_1 :: Language -> Doc AnsiStyle
packageNotFound_1 = \case
  Language
Romanian   -> Doc AnsiStyle
"Nu s-a găsit nici un pachet."
  Language
Vietnamese -> Doc AnsiStyle
"Không tím thấy gói."
  Language
Czech      -> Doc AnsiStyle
"Nebyly nalezeny žádné balíčky."
  Language
Korean     -> Doc AnsiStyle
"패키지를 찾을 수 없습니다."
  Language
_          -> Doc AnsiStyle
"No packages found."

-- https://github.com/fosskers/aura/issues/498
connectFailure_1 :: Language -> Doc AnsiStyle
connectFailure_1 :: Language -> Doc AnsiStyle
connectFailure_1 = \case
  Language
Polish    -> Doc AnsiStyle
"Nie udało się nawiązać połączenia z AUR. Czy jesteś połączony z internetem?"
  Language
Arabic    -> Doc AnsiStyle
"هل انت متصل بالانترنت؟ .AURفشل الاتصال بـ"
  Language
Spanish   -> Doc AnsiStyle
"No se pudo contactar con el AUR. ¿Tienes conexión a internet?"
  Language
Italian   -> Doc AnsiStyle
"Non è stato possibile contattare l'AUR. Il computer è connesso ad internet?"
  Language
Dutch     -> Doc AnsiStyle
"Er kan geen verbinding worden gemaakt met de AUR. Bent u verbonden met het internet?"
  Language
Ukrainian -> Doc AnsiStyle
"Не вдалося зв'язатись з AUR. У вас є підключення до інтернету?"
  Language
Romanian  -> Doc AnsiStyle
"Nu s-a putut contacta AUR. Sunteți conectat pe Internet?"
  Language
Vietnamese -> Doc AnsiStyle
"Mất kết nối tới AUR. Bạn có kết nối mạng không?"
  Language
Czech     -> Doc AnsiStyle
"Nepodařilo se kontaktovat AUR server. Máte připojení k internetu?"
  Language
Korean    -> Doc AnsiStyle
"AUR에 접근하지 못했습니다. 인터넷 연결 상태를 확인하십시오."
  Language
_         -> Doc AnsiStyle
"Failed to contact the AUR. Do you have an internet connection?"

dependencyLookup_1 :: Text -> Language -> Doc AnsiStyle
dependencyLookup_1 :: Text -> Language -> Doc AnsiStyle
dependencyLookup_1 Text
t = \case
  Language
Romanian  -> [Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep [Doc AnsiStyle
"A fost o problemă cu analiza recursivă de dependențe:", Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t]
  Language
Vietnamese -> [Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep [Doc AnsiStyle
"Có lỗi trong quá trình tìm kiếm gói phụ thuộc đệ quy:", Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t]
  Language
Czech     -> [Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep [Doc AnsiStyle
"Při rekurzivním vyhledávání závislostí došlo k problému:", Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t]
  Language
Korean    -> [Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep [Doc AnsiStyle
"재귀 종속성 조회 중 문제가 발생했습니다:", Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t]
  Language
_         -> [Doc AnsiStyle] -> Doc AnsiStyle
forall ann. [Doc ann] -> Doc ann
vsep [Doc AnsiStyle
"There was an issue during recursive dependency lookup:", Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
t]

miscAURFailure_1 :: Language -> Doc AnsiStyle
miscAURFailure_1 :: Language -> Doc AnsiStyle
miscAURFailure_1 = \case
  Language
Polish     -> Doc AnsiStyle
"Wystąpił nieznany błąd podczas próby łączenia z AUR."
  Language
Arabic     -> Doc AnsiStyle
".بطريقة غير معروفة AURفشل الاتصال بـ"
  Language
Spanish    -> Doc AnsiStyle
"El contacto con el AUR falló de alguna manera desconocida."
  Language
Italian    -> Doc AnsiStyle
"C'è stato un errore sconosciuto nel contattare l'AUR."
  Language
Dutch      -> Doc AnsiStyle
"Er kan om onbekende reden geen verbinding worden gemaakt met de AUR."
  Language
Ukrainian  -> Doc AnsiStyle
"Зв'язок з AUR було обірвано невідомим чином."
  Language
Romanian   -> Doc AnsiStyle
"Nu s-a putut contacta AUR dintr-un motiv necunoscut."
  Language
Vietnamese -> Doc AnsiStyle
"Bất ngờ không thể kết nối tới AUR."
  Language
Czech      -> Doc AnsiStyle
"Kontaktování AUR se nezdařilo neznámým způsobem."
  Language
Korean     -> Doc AnsiStyle
"알 수 없는 문제로 AUR에 접근하지 못했습니다."
  Language
_          -> Doc AnsiStyle
"Contacting the AUR failed in some unknown way."

miscAURFailure_3 :: Language -> Doc AnsiStyle
miscAURFailure_3 :: Language -> Doc AnsiStyle
miscAURFailure_3 = \case
  Language
Polish     -> Doc AnsiStyle
"Plik JSON zwrócony z AUR nie mógł zostać rozszyfrowany."
  Language
Arabic     -> Doc AnsiStyle
".AURالذي تم ارجاعه من اﻟ JSONفشل فك شفرة اﻟ"
  Language
Spanish    -> Doc AnsiStyle
"El JSON devuelto por el servidor AUR no se pudo decodificar."
  Language
Ukrainian  -> Doc AnsiStyle
"JSON, який повернувся з сервера AUR, неможливо розшифрувати."
  Language
Romanian   -> Doc AnsiStyle
"JSON-ul întors de server-ul AUR nu putea fi decodat."
  Language
Vietnamese -> Doc AnsiStyle
"Không thể giải mã tệp JSON lấy từ máy chủ AUR."
  Language
Czech      -> Doc AnsiStyle
"JSON vrácený ze serveru AUR nelze dekódovat."
  Language
Korean     -> Doc AnsiStyle
"AUR 서버에서 받은 JSON을 디코딩할 수 없습니다."
  Language
Dutch      -> Doc AnsiStyle
"De AUR-server stuurde JSON terug die niet kan worden ontsleuteld."
  Language
_          -> Doc AnsiStyle
"The JSON returned from the AUR server could not be decoded."

infoFields :: Language -> [Text]
infoFields :: Language -> [Text]
infoFields = [Language -> Text] -> Language -> [Text]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [ Language -> Text
Fields.repository
                      , Language -> Text
Fields.name
                      , Language -> Text
Fields.version
                      , Language -> Text
Fields.aurStatus
                      , Language -> Text
Fields.maintainer
                      , Language -> Text
Fields.projectUrl
                      , Language -> Text
Fields.aurUrl
                      , Language -> Text
Fields.license
                      , Language -> Text
Fields.dependsOn
                      , Language -> Text
Fields.buildDeps
                      , Language -> Text
Fields.votes
                      , Language -> Text
Fields.popularity
                      , Language -> Text
Fields.description
                      ]

outOfDateMsg :: Maybe Int -> Language -> Doc AnsiStyle
outOfDateMsg :: Maybe Int -> Language -> Doc AnsiStyle
outOfDateMsg (Just Int
_) = Doc AnsiStyle -> Doc AnsiStyle
red (Doc AnsiStyle -> Doc AnsiStyle)
-> (Language -> Doc AnsiStyle) -> Language -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
    Language
Japanese   -> Doc AnsiStyle
"AURで要更新!"
    Language
Arabic     -> Doc AnsiStyle
"!انتهت صلاحيته"
    Language
Polish     -> Doc AnsiStyle
"Nieaktualny!"
    Language
Croatian   -> Doc AnsiStyle
"Zastarjelo!"
    Language
Swedish    -> Doc AnsiStyle
"Utdaterad!"
    Language
German     -> Doc AnsiStyle
"Veraltet!"
    Language
Spanish    -> Doc AnsiStyle
"¡Desactualizado!"
    Language
Portuguese -> Doc AnsiStyle
"Desatualizado!"
    Language
French     -> Doc AnsiStyle
"Périmé !"
    Language
Russian    -> Doc AnsiStyle
"Устарел!"
    Language
Italian    -> Doc AnsiStyle
"Non aggiornato all'ultima versione!"
    Language
Serbian    -> Doc AnsiStyle
"Застарео!"
    Language
Norwegian  -> Doc AnsiStyle
"Utdatert!"
    Language
Indonesia  -> Doc AnsiStyle
"Ketinggalan Zaman!"
    Language
Chinese    -> Doc AnsiStyle
"过期!"
    Language
Esperanto  -> Doc AnsiStyle
"Neĝisdata!"
    Language
Dutch      -> Doc AnsiStyle
"Verouderd!"
    Language
Ukrainian  -> Doc AnsiStyle
"Застарів!"
    Language
Romanian   -> Doc AnsiStyle
"Neactualizat!"
    Language
Vietnamese -> Doc AnsiStyle
"Đã cũ!"
    Language
Czech      -> Doc AnsiStyle
"Zastaralý!"
    Language
Korean     -> Doc AnsiStyle
"최신 버전이 아님!"
    Language
_          -> Doc AnsiStyle
"Out of Date!"

outOfDateMsg Maybe Int
Nothing = Doc AnsiStyle -> Doc AnsiStyle
green (Doc AnsiStyle -> Doc AnsiStyle)
-> (Language -> Doc AnsiStyle) -> Language -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
    Language
Japanese   -> Doc AnsiStyle
"最新"
    Language
Arabic     -> Doc AnsiStyle
"حتى الوقت الرهن"
    Language
Polish     -> Doc AnsiStyle
"Aktualny"
    Language
Croatian   -> Doc AnsiStyle
"Ažurirano"
    Language
Swedish    -> Doc AnsiStyle
"Aktuell"
    Language
German     -> Doc AnsiStyle
"Aktuell"
    Language
Spanish    -> Doc AnsiStyle
"Actualizado"
    Language
Portuguese -> Doc AnsiStyle
"Atualizado"
    Language
French     -> Doc AnsiStyle
"À jour"
    Language
Russian    -> Doc AnsiStyle
"Новейший"
    Language
Italian    -> Doc AnsiStyle
"Aggiornato all'ultima versione"
    Language
Serbian    -> Doc AnsiStyle
"Ажуран"
    Language
Norwegian  -> Doc AnsiStyle
"Oppdatert"
    Language
Indonesia  -> Doc AnsiStyle
"Mutakhir"
    Language
Chinese    -> Doc AnsiStyle
"最新"
    Language
Esperanto  -> Doc AnsiStyle
"Ĝisdata"
    Language
Dutch      -> Doc AnsiStyle
"Actueel"
    Language
Ukrainian  -> Doc AnsiStyle
"Найновіший"
    Language
Romanian   -> Doc AnsiStyle
"Actializat"
    Language
Vietnamese -> Doc AnsiStyle
"Mới nhất"
    Language
Czech      -> Doc AnsiStyle
"Aktuální"
    Language
Korean     -> Doc AnsiStyle
"최신 버전"
    Language
_          -> Doc AnsiStyle
"Up to Date"

-- NEEDS TRANSLATION
orphanedMsg :: Maybe Text -> Language -> Doc AnsiStyle
orphanedMsg :: Maybe Text -> Language -> Doc AnsiStyle
orphanedMsg (Just Text
m) = Doc AnsiStyle -> Language -> Doc AnsiStyle
forall a b. a -> b -> a
const (Text -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty Text
m)
orphanedMsg Maybe Text
Nothing = Doc AnsiStyle -> Doc AnsiStyle
red (Doc AnsiStyle -> Doc AnsiStyle)
-> (Language -> Doc AnsiStyle) -> Language -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
    Language
Japanese   -> Doc AnsiStyle
"孤児です!"
    Language
Arabic     -> Doc AnsiStyle
"!حزمة يتيمة"
    Language
Polish     -> Doc AnsiStyle
"Osierocony!"
    Language
Croatian   -> Doc AnsiStyle
"Nema roditelja!"
    Language
German     -> Doc AnsiStyle
"Verwaist!"
    Language
Spanish    -> Doc AnsiStyle
"¡Huérfano!"
    Language
Norwegian  -> Doc AnsiStyle
"Foreldreløs!"
    Language
Portuguese -> Doc AnsiStyle
"Órfão!"
    Language
French     -> Doc AnsiStyle
"Abandonné !"
    Language
Russian    -> Doc AnsiStyle
"Осиротевший!"
    Language
Italian    -> Doc AnsiStyle
"Orfano!"
    Language
Indonesia  -> Doc AnsiStyle
"Tak dipelihara!"
    Language
Chinese    -> Doc AnsiStyle
"孤包!"
    Language
Swedish    -> Doc AnsiStyle
"Föräldralös!"
    Language
Esperanto  -> Doc AnsiStyle
"Orfita!"
    Language
Dutch      -> Doc AnsiStyle
"Onteigend!"
    Language
Ukrainian  -> Doc AnsiStyle
"Осиротів!"
    Language
Romanian   -> Doc AnsiStyle
"Orfan!"
    Language
Vietnamese -> Doc AnsiStyle
"Gói lẻ!"
    Language
Czech      -> Doc AnsiStyle
"Opuštěno!"
    Language
Korean     -> Doc AnsiStyle
"관리되지 않는 패키지입니다!"
    Language
_          -> Doc AnsiStyle
"Orphaned!"

-----------------------
-- Aura/State functions
-----------------------
-- NEEDS TRANSLATION
saveState_1 :: Language -> Doc AnsiStyle
saveState_1 :: Language -> Doc AnsiStyle
saveState_1 = \case
    Language
Japanese   -> Doc AnsiStyle
"パッケージ状態の保存完了。"
    Language
Arabic     -> Doc AnsiStyle
". حالة الحزمة محفوظة"
    Language
Polish     -> Doc AnsiStyle
"Zachowano stan pakietów"
    Language
Croatian   -> Doc AnsiStyle
"Stanje paketa spremljeno."
    Language
German     -> Doc AnsiStyle
"Paketzustand gesichert."
    Language
Spanish    -> Doc AnsiStyle
"Estado del paquete salvado."
    Language
Serbian    -> Doc AnsiStyle
"Сачувано стање пакета."
    Language
Norwegian  -> Doc AnsiStyle
"Lagret pakketilstand."
    Language
Italian    -> Doc AnsiStyle
"Stato del pacchetto salvato."
    Language
Portuguese -> Doc AnsiStyle
"Estado de pacote salvo."
    Language
French     -> Doc AnsiStyle
"État des paquets sauvegardé."
    Language
Russian    -> Doc AnsiStyle
"Состояние пакетов сохранено."
    Language
Indonesia  -> Doc AnsiStyle
"Kondisi paket tersimpan."
    Language
Chinese    -> Doc AnsiStyle
"已保存包状态。"
    Language
Swedish    -> Doc AnsiStyle
"Det lokala pakettillståndet har sparats."
    Language
Esperanto  -> Doc AnsiStyle
"Konservita stato de pakaĵo."
    Language
Dutch      -> Doc AnsiStyle
"De pakketstatus is bewaard."
    Language
Ukrainian  -> Doc AnsiStyle
"Стан пакунків збережено."
    Language
Romanian   -> Doc AnsiStyle
"Stare de pachete salvată."
    Language
Vietnamese -> Doc AnsiStyle
"Đã lưu trạng thái gói."
    Language
Czech      -> Doc AnsiStyle
"Stav balíčku byl uložen."
    Language
Korean     -> Doc AnsiStyle
"패키지 상태가 저장되었습니다."
    Language
_          -> Doc AnsiStyle
"Saved package state."

-- NEEDS TRANSLATION
restoreState_1 :: Language -> Doc AnsiStyle
restoreState_1 :: Language -> Doc AnsiStyle
restoreState_1 = \case
    Language
Japanese   -> Doc AnsiStyle
"対象バージョンがないパッケージ:"
    Language
Arabic     -> Doc AnsiStyle
":اصدارات الرجوع المطلوبة غير متوفرة للحزمة التالية"
    Language
Polish     -> Doc AnsiStyle
"Starsze wersje nie są dostępne dla:"
    Language
Croatian   -> Doc AnsiStyle
"Tražene stare verzije nisu dostupne za:"
    Language
German     -> Doc AnsiStyle
"Gewünschte Downgrade-Versionen nicht verfügbar für:"
    Language
Spanish    -> Doc AnsiStyle
"Versiones anteriores no disponibles para:"
    Language
Serbian    -> Doc AnsiStyle
"Захтеване старе верзије нису доступне за:"
    Language
Norwegian  -> Doc AnsiStyle
"De spesifiserte nedgraderingsversjonene er ikke tilgjengelig for:"
    Language
Italian    -> Doc AnsiStyle
"Non sono disponibili versioni precedenti a cui tornare per:"
    Language
Portuguese -> Doc AnsiStyle
"Versões anteriores requisitadas não disponívels para:"
    Language
French     -> Doc AnsiStyle
"Version antérieure requise non disponible pour :"
    Language
Russian    -> Doc AnsiStyle
"Запрошенные версии для отката не доступны для:"
    Language
Indonesia  -> Doc AnsiStyle
"Versi yang diturunkan tidak tersedia untuk: "
    Language
Chinese    -> Doc AnsiStyle
"请求的降级版本对以下包不可用:"
    Language
Swedish    -> Doc AnsiStyle
"Den begärda nedgraderingen finns inte tillgänglig för:"
    Language
Esperanto  -> Doc AnsiStyle
"Petitajn malpromociajn versiojn ne estas disponebla de:"
    Language
Dutch      -> Doc AnsiStyle
"De verzochte afwaardeerversies zijn niet beschikbaar voor:"
    Language
Ukrainian  -> Doc AnsiStyle
"Запитані версії для відкату не доступні для:"
    Language
Romanian   -> Doc AnsiStyle
"Versiunea solicitată pentru retrogradare nu este disponibilă pentru:"
    Language
Vietnamese -> Doc AnsiStyle
"Không thể hạ cấp cho:"
    Language
Czech      -> Doc AnsiStyle
"Požadované nižší verze nejsou k dispozici pro:"
    Language
Korean     -> Doc AnsiStyle
"요청한 다운그레이드 버전은 다음 패키지에 사용할 수 없습니다:"
    Language
_          -> Doc AnsiStyle
"Requested downgrade versions not available for:"

restoreState_2 :: Language -> Doc AnsiStyle
restoreState_2 :: Language -> Doc AnsiStyle
restoreState_2 = \case
    Language
Japanese   -> Doc AnsiStyle
"保存されたパッケージ状態がない。作るには「-B」を。"
    Language
Arabic     -> Doc AnsiStyle
"(لحفظ الحالة الحالية -B استخدم) .عدم وجود حالة محفوظة للرجوع إليها"
    Language
Polish     -> Doc AnsiStyle
"Brak zapisanych stanów do przywrócenia. (Użyj -B by zapisać aktualny stan)"
    Language
Spanish    -> Doc AnsiStyle
"No hay estados guardados para ser restaurados. (Utilice -B para guardar el estado actual)"
    Language
Portuguese -> Doc AnsiStyle
"Nenhum estado disponível para ser recuperado. (Utilize -B para salvar o estado atual)"
    Language
Russian    -> Doc AnsiStyle
"Нет сохраненных состояний для восстановления. (Используйте -B для сохранения текущего состояния)"
    Language
Italian    -> Doc AnsiStyle
"Nessuno stato precedente a cui tornare. (Usa -B per salvare lo stato attuale)"
    Language
Chinese    -> Doc AnsiStyle
"没有要恢复的已保存状态。(使用 -B 保存当前状态)"
    Language
Swedish    -> Doc AnsiStyle
"Inga sparade tillstånd att återhämta. (Använd -B för att spara det nuvarande tillståndet)"
    Language
Esperanto  -> Doc AnsiStyle
"Ne konservitaj statoj restaŭros. (Uzu -B konservi la aktualan staton)"
    Language
Dutch      -> Doc AnsiStyle
"Er zijn geen bewaarde statussen om te herstellen. (ken -B toe om de huidige status te bewaren)"
    Language
Ukrainian  -> Doc AnsiStyle
"Немає збережених станів для відновлення. (Викоривуйте -B для збереження теперішнього стану)"
    Language
Romanian   -> Doc AnsiStyle
"Nu există vreo stare de recuperat. (Folosiți -B pentru a salva starea actuală)"
    Language
Vietnamese -> Doc AnsiStyle
"Không có trạng thái nào có thể lưu. (Dùng -B để lưu trạng thái hiện tại)"
    Language
Czech      -> Doc AnsiStyle
"Žádné uložené stavy k obnovení. (Pro uložení aktuálního stavu použijte -B)"
    Language
Korean     -> Doc AnsiStyle
"복원할 패키지 상태가 없습니다. (-B를 사용해 현재 상태를 저장)"
    Language
_          -> Doc AnsiStyle
"No saved states to be restored. (Use -B to save the current state)"

-- NEEDS TRANSLATION
reinstallAndRemove_1 :: Language -> Doc AnsiStyle
reinstallAndRemove_1 :: Language -> Doc AnsiStyle
reinstallAndRemove_1 = \case
    Language
Japanese   -> Doc AnsiStyle
"パッケージを変更する必要はありません。"
    Language
Arabic     -> Doc AnsiStyle
".لا يوجد حزمة تحتاج التغير"
    Language
Polish     -> Doc AnsiStyle
"Żaden pakiet nie wymaga zmian"
    Language
Croatian   -> Doc AnsiStyle
"Nema paketa kojima su potrebne izmjene."
    Language
German     -> Doc AnsiStyle
"Keine Pakete brauchen Änderungen."
    Language
Spanish    -> Doc AnsiStyle
"Ningún paquete necesita cambios."
    Language
Serbian    -> Doc AnsiStyle
"Ниједан пакет не захтева измене."
    Language
Norwegian  -> Doc AnsiStyle
"Ingen pakker trenger forandring."
    Language
Italian    -> Doc AnsiStyle
"Nessun pacchetto necessita di cambiamenti."
    Language
Portuguese -> Doc AnsiStyle
"Nenhum pacote requer alteração."
    Language
French     -> Doc AnsiStyle
"Aucun paquet n'a besoin de changement."
    Language
Russian    -> Doc AnsiStyle
"Пакеты не нуждаются в изменениях."
    Language
Indonesia  -> Doc AnsiStyle
"Tidak ada paket yang diubah."
    Language
Chinese    -> Doc AnsiStyle
"没有包需要改变。"
    Language
Swedish    -> Doc AnsiStyle
"Inga paket behöver ändras."
    Language
Esperanto  -> Doc AnsiStyle
"Ne pakaĵoj devas ŝanĝiĝi."
    Language
Dutch      -> Doc AnsiStyle
"Er zijn geen pakketten die aangepast moeten worden."
    Language
Ukrainian  -> Doc AnsiStyle
"Пакунки не потребують оновлення."
    Language
Romanian   -> Doc AnsiStyle
"Nu trebuie schimbat nici un pachet."
    Language
Vietnamese -> Doc AnsiStyle
"Không có gói nào cần thay đổi."
    Language
Czech      -> Doc AnsiStyle
"Žádné balíčky není třeba měnit."
    Language
Korean     -> Doc AnsiStyle
"패키지를 변경할 필요가 없습니다."
    Language
_          -> Doc AnsiStyle
"No packages need changing."

--------------------------------------
-- Aura/Settings/BadPackages functions
--------------------------------------
whoIsBuildUser_1 :: Language -> Doc AnsiStyle
whoIsBuildUser_1 :: Language -> Doc AnsiStyle
whoIsBuildUser_1 = \case
    Language
Polish     -> Doc AnsiStyle
"Nie można określić z którego konta użytkownika chcesz budować."
    Language
Arabic     -> Doc AnsiStyle
".لا يمكن تحديد حساب المستخدم الذي سيتم البناء به"
    Language
Spanish    -> Doc AnsiStyle
"No se puede determinar el usuario que ejecutará la compilación."
    Language
Portuguese -> Doc AnsiStyle
"Não foi possível determinal o usuário que executará a compilação."
    Language
Russian    -> Doc AnsiStyle
"Не удается определить, от имени какого пользователя производить сборку."
    Language
Italian    -> Doc AnsiStyle
"Non è stato possibile determinare l'utente che eseguirà la compilazione."
    Language
Esperanto  -> Doc AnsiStyle
"Ne povas decidi, per kiu konto de uzanto munti."
    Language
Dutch      -> Doc AnsiStyle
"Er kan niet worden vastgesteld met welk gebruikersaccount er gebouwd dient te worden."
    Language
Ukrainian  -> Doc AnsiStyle
"Не вдається визначити користувача, від імені якого буде проводитись збірка."
    Language
Romanian   -> Doc AnsiStyle
"Nu se poate determina cu care cont de utilizator să se compileze."
    Language
Vietnamese -> Doc AnsiStyle
"Không thể xác định tài khoản người dùng nào để build."
    Language
Czech      -> Doc AnsiStyle
"Nelze určit, se kterým uživatelským účtem se má provezt build."
    Language
Korean     -> Doc AnsiStyle
"사용자가 컴파일할 것인지 확일할 수 없습니다."
    Language
_          -> Doc AnsiStyle
"Can't determine which user account to build with."

------------------------
-- Aura/Pacman functions
------------------------
confParsing_1 :: Language -> Doc AnsiStyle
confParsing_1 :: Language -> Doc AnsiStyle
confParsing_1 = \case
    Language
Polish     -> Doc AnsiStyle
"Nie udało się odczytać twojego pliku pacman.conf"
    Language
Arabic     -> Doc AnsiStyle
".الخاص بك pacman.confفشل تحليل ملف اﻟ"
    Language
Spanish    -> Doc AnsiStyle
"No fue posible analizar su archivo pacman.conf."
    Language
Portuguese -> Doc AnsiStyle
"Não foi possível interpretar o arquivo pacman.conf ."
    Language
Russian    -> Doc AnsiStyle
"Не удается распознать формат вашего файла pacman.conf."
    Language
Italian    -> Doc AnsiStyle
"Non è stato possibile analizzare il file pacman.conf."
    Language
Esperanto  -> Doc AnsiStyle
"Ne kapablas sintaske analizi vian dosieron, pacman.conf."
    Language
Dutch      -> Doc AnsiStyle
"Uw pacman.conf-bestand kan niet worden verwerkt."
    Language
Ukrainian  -> Doc AnsiStyle
"Не вдалось зрозуміти вміст файлу pacman.conf."
    Language
Romanian   -> Doc AnsiStyle
"Nu se poate analiza fișierul pacman.conf."
    Language
Vietnamese -> Doc AnsiStyle
"Không thể lấy dữ liệu từ tệp pacman.conf của bạn."
    Language
Czech      -> Doc AnsiStyle
"Nelze analyzovat soubor pacman.conf."
    Language
Korean     -> Doc AnsiStyle
"pacman.conf 파일 분석에 실패했습니다."
    Language
_          -> Doc AnsiStyle
"Unable to parse your pacman.conf file."

provides_1 :: PkgName -> Language -> Doc AnsiStyle
provides_1 :: PkgName -> Language -> Doc AnsiStyle
provides_1 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle)
-> (PkgName -> Text) -> PkgName -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PkgName -> Text
pnName -> Doc AnsiStyle
pro) = \case
    Language
Polish     -> Doc AnsiStyle
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"jest wymagany/a jako zależność, dostarczana przez wiele pakietów. Proszę wybrać jeden:"
    Language
Arabic     -> Doc AnsiStyle
":مطلوب باعتباره تبعية ، والتي يتم توفيرها بواسطة حزم متعددة. رجاءا اختر واحدة" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
pro
    Language
Spanish    -> Doc AnsiStyle
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"se requiere como una dependencia, que es proporcionada por múltiples paquetes. Por favor, seleccione uno:"
    Language
Italian    -> Doc AnsiStyle
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"è richiesto come dipendenza; si trova in molteplici pacchetti. Selezionarne uno:"
    Language
Dutch      -> Doc AnsiStyle
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"is vereist als afhankelijkheid, maar wordt door meerdere pakketten aangeleverd. Kies 1 pakket:"
    Language
Ukrainian  -> Doc AnsiStyle
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"потрібен як залежність, яка надається декількома пакунками. Оберіть один з них:"
    Language
Romanian   -> Doc AnsiStyle
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"este necesar ca dependență, care e provizionat de mai multe pachete. Selectați unul dintre ele:"
    Language
Vietnamese -> Doc AnsiStyle
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"là gói phụ thuộc, được cung cấp từ nhiều gói khác. Hãy chọn một:"
    Language
Czech      -> Doc AnsiStyle
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"je vyžadována jako závislost, kterou poskytuje několik balíčků. Prosím vyberte jeden:"
    Language
Korean     -> Doc AnsiStyle
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"는 종속성으로 필요하며 여러 패키지에서 제공됩니다. 다음 중 하나를 선택하십시오:"
    Language
_          -> Doc AnsiStyle
pro Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"is required as a dependency, which is provided by multiple packages. Please select one:"

----------------------------------
-- Aura/Pkgbuild/Editing functions
----------------------------------
hotEdit_1 :: PkgName -> Language -> Doc AnsiStyle
hotEdit_1 :: PkgName -> Language -> Doc AnsiStyle
hotEdit_1 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt (Text -> Doc AnsiStyle)
-> (PkgName -> Text) -> PkgName -> Doc AnsiStyle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PkgName -> Text
pnName -> Doc AnsiStyle
p) = \case
    Language
Japanese   -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"のPKGBUILDを編成しますか?"
    Language
Polish     -> Doc AnsiStyle
"Czy chcesz edytować PKGBUILD " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
    Language
Arabic     -> Doc AnsiStyle
"؟" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"التابع ﻟ PKGBUILDهل تريد ان تعدل اﻟ"
    Language
Croatian   -> Doc AnsiStyle
"Želite li izmjeniti PKGBUILD " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
    Language
Swedish    -> Doc AnsiStyle
"Vill du ändra PKGBUILD-filen ifrån " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
    Language
German     -> Doc AnsiStyle
"Möchten Sie die PKGBUILD-Datei für " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" bearbeiten?"
    Language
Spanish    -> Doc AnsiStyle
"¿Deseas editar el PKGBUILD de " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
    Language
Portuguese -> Doc AnsiStyle
"Deseja editar o PKGBUILD de " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
    Language
French     -> Doc AnsiStyle
"Voulez-vous éditer le PKGBUILD de " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" ?"
    Language
Russian    -> Doc AnsiStyle
"Отредактировать PKGBUILD пакета " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
    Language
Italian    -> Doc AnsiStyle
"Modificare il PKGBUILD di " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
    Language
Serbian    -> Doc AnsiStyle
"Желите ли да измените PKGBUILD за " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
    Language
Norwegian  -> Doc AnsiStyle
"Vil du endre PKGBUILD for " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
    Language
Indonesia  -> Doc AnsiStyle
"Apakah anda ingin menyunting PKGBUILD untuk paket " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
    Language
Chinese    -> Doc AnsiStyle
"你希望编辑 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" 的 PKGBUILD 文件吗?"
    Language
Esperanto  -> Doc AnsiStyle
"Ĉu vi volas redakti la PKGBUILD de " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
    Language
Dutch      -> Doc AnsiStyle
"Wilt u het PKGBUILD-bestand van " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" bewerken?"
    Language
Ukrainian  -> Doc AnsiStyle
"Бажаєте відредагувати PKGBUILD для пакунку " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
    Language
Romanian   -> Doc AnsiStyle
"Doriți să modificați PKGBUILD-ul pachetului " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
    Language
Vietnamese -> Doc AnsiStyle
"Bạn có muốn chỉnh sửa PKGBUILD của " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
    Language
Czech      -> Doc AnsiStyle
"Chcete upravit PKGBUILD z " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
    Language
Korean     -> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"의 PKGBUILD를 편집하시겠습니까?"
    Language
_          -> Doc AnsiStyle
"Would you like to edit the PKGBUILD of " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"

hotEdit_2 :: Language -> Doc AnsiStyle
hotEdit_2 :: Language -> Doc AnsiStyle
hotEdit_2 = \case
  Language
Polish     -> Doc AnsiStyle
"Czy chcesz edytować plik .install?"
  Language
Arabic     -> Doc AnsiStyle
"؟.installهل تريد تعديل ملف اﻟ"
  Language
Spanish    -> Doc AnsiStyle
"¿Desea editar el archivo .install?"
  Language
Ukrainian  -> Doc AnsiStyle
"Бажаєте відредагувати файл .intall?"
  Language
Romanian   -> Doc AnsiStyle
"Doriți să modificați fișierul .install?"
  Language
Vietnamese -> Doc AnsiStyle
"Bạn có muốn chỉnh sửa tệp .install?"
  Language
Czech      -> Doc AnsiStyle
"Chcete upravit soubor .install?"
  Language
Korean     -> Doc AnsiStyle
".install 파일을 수정하시겠습니까?"
  Language
Dutch      -> Doc AnsiStyle
"Wilt u het .install-bestand bewerken?"
  Language
_          -> Doc AnsiStyle
"Would you like to edit the .install file?"

hotEdit_3 :: FilePath -> Language -> Doc AnsiStyle
hotEdit_3 :: String -> Language -> Doc AnsiStyle
hotEdit_3 String
fp = \case
  Language
Polish     -> Doc AnsiStyle
"Czy chcesz edytować " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
  Language
Arabic     -> Doc AnsiStyle
"؟" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
" هل تريد التعديل"
  Language
Spanish    -> Doc AnsiStyle
"¿Desea editar " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
  Language
Ukrainian  -> Doc AnsiStyle
"Бажаєте відредагувати " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
  Language
Romanian   -> Doc AnsiStyle
"Doriți să modificați " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
  Language
Vietnamese -> Doc AnsiStyle
"Bạn có muốn chỉnh sửa " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
  Language
Czech      -> Doc AnsiStyle
"Chcete upravit " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"
  Language
Korean     -> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"을(를) 수정하시겠습니까?"
  Language
Dutch      -> Doc AnsiStyle
"Wilt u " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"bewerken?"
  Language
_          -> Doc AnsiStyle
"Would you like to edit " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> String -> Doc AnsiStyle
forall a ann. Pretty a => a -> Doc ann
pretty String
fp Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall a. Semigroup a => a -> a -> a
<> Doc AnsiStyle
"?"

------------------------------
-- Pkgbuild Security functions
------------------------------
security_1 :: PkgName -> Language -> Doc AnsiStyle
security_1 :: PkgName -> Language -> Doc AnsiStyle
security_1 (PkgName Text
p) = \case
  Language
Polish    -> Doc AnsiStyle
"PKGBUILD dla" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"był zbyt zawiły do odczytania - może zawierać złośliwy kod."
  Language
Arabic    -> Doc AnsiStyle
".كان معقدا جدا للتحليل - يمكن أن يكون تعتيم مشوش للشفرة" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"تبع PKGBUILDاﻟ"
  Language
Spanish   -> Doc AnsiStyle
"El PKGBUILD de" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"era demasiado complejo de analizar - puede estar ofuscando código malicioso."
  Language
Italian   -> Doc AnsiStyle
"Il PKGBUILD di" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"è troppo complesso per essere analizzato - è possibile che stia offuscando codice malevolo."
  Language
Dutch     -> Doc AnsiStyle
"Het PKGBUILD-bestand van" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
" was te complex om te verwerken. Het bestand bevat mogelijk verborgen schadelijke code."
  Language
Ukrainian -> Doc AnsiStyle
"PKGBUILD пакунку" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"був надто складним для аналізу - він може містити замаскований шкідливий код."
  Language
Romanian  -> Doc AnsiStyle
"PKGBUILD-ul pachetului" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"este prea complicat de analizat - ar putea sa acopere cod rău intenționat."
  Language
Vietnamese -> Doc AnsiStyle
"PKGBUILD của" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"quá khó để đọc - nó có thể chứa đoạn mã nguy hiểm."
  Language
Czech     -> Doc AnsiStyle
"PKGBUILD z" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"byl příliš složitý na analýzu - může obsahovat matoucí škodlivý kód."
  Language
Korean    -> Doc AnsiStyle
"이 " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
" PKGBUILD는 너무 복잡하여 분석할 수 없습니다 - 난독화된 코드일 수 있습니다."
  Language
_         -> Doc AnsiStyle
"The PKGBUILD of" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"was too complex to parse - it may be obfuscating malicious code."

security_2 :: Text -> Language -> Doc AnsiStyle
security_2 :: Text -> Language -> Doc AnsiStyle
security_2 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt -> Doc AnsiStyle
t) = \case
  Language
Polish    -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"może zostać użyty do pobrania arbitralnych skryptów, które nie są śledzone przez ten PKGBUILD."
  Language
Arabic    -> Doc AnsiStyle
".هذه PKGBUILDيمكن ان يحمل ملفات عشروتىية ليست مسجلة باﻟ" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
t
  Language
Spanish   -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"se puede usar para descargar scripts arbitrarios que este PKGBUILD no rastrea."
  Language
Italian   -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"può essere usato per scaricare script arbitrari non tracciati da questo PKGBUILD."
  Language
Dutch     -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"kan gebruikt worden om willekeurige scripts te downloaden die niet worden bijgehouden door dit PKGBUILD-bestand."
  Language
Ukrainian -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"може завантажувати довільні скріпти, які не відстежуються цим PKGBUILD."
  Language
Romanian  -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"se poate folosi pentru a descărca scripturi neurmărite de acest PKGBUILD."
  Language
Vietnamese -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"có thể dùng để tải xuống các tập lệnh sẽ không được kiểm soát bởi PKGBUILD."
  Language
Czech     -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"lze použít ke stažení libovolných skriptů, které tento PKGBUILD nesleduje."
  Language
Korean    -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"은(는) PKGBUILD에서 추적되지 않는 임의 스크립트를 다운로드하는 데 사용할 수 있습니다."
  Language
_         -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"can be used to download arbitrary scripts that aren't tracked by this PKGBUILD."

security_3 :: Text -> Language -> Doc AnsiStyle
security_3 :: Text -> Language -> Doc AnsiStyle
security_3 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt -> Doc AnsiStyle
t) = \case
  Language
Polish    -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"może zostać użyty do wykonywania arbitralnego kodu, który nie jest śledzony przez ten PKGBUILD."
  Language
Arabic    -> Doc AnsiStyle
".هذه PKGBUILDيمكن ان يستعمل ملفات عشروتىية ليست مسجلة باﻟ" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
t
  Language
Spanish   -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"se puede usar para ejecutar código arbitrario que este PKGBUILD no rastrea."
  Language
Italian   -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"può essere usato per eseguire codice arbitrario non tracciato da questo PKGBUILD."
  Language
Dutch     -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"kan gebruikt worden om willekeurige code uit te voeren die niet worden bijgehouden door dit PKGBUILD-bestand."
  Language
Ukrainian -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"може виконувати довільний код, який не відстежуються цим PKGBUILD."
  Language
Romanian  -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"se poate folosi pentru a executa cod arbitrar neurmărit de acest PKGBUILD."
  Language
Vietnamese -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"có thể dùng để chạy các đoạn mã không được kiểm soát bởi PKGBUILD. "
  Language
Czech     -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"lze použít ke spuštění libovolného kódu, který tento PKGBUILD nesleduje."
  Language
Korean    -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"은(는) PKGBUILD에서 추적되지 않는 임의 스크립트를 실행하는 데 사용할 수 있습니다."
  Language
_         -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"can be used to execute arbitrary code not tracked by this PKGBUILD."

security_4 :: Text -> Language -> Doc AnsiStyle
security_4 :: Text -> Language -> Doc AnsiStyle
security_4 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt -> Doc AnsiStyle
t) = \case
  Language
Polish    -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"wskazuje na to, że ktoś może próbować uzyskać dostęp root'a do twojej maszyny."
  Language
Arabic    -> Doc AnsiStyle
".تشير ان شخصا ما يحاول الوصول الى قوت المسؤول على جهازك" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
t
  Language
Spanish   -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"indica que alguien puede estar intentando obtener acceso de root a su máquina."
  Language
Italian   -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"indica che forse qualcuno sta cercando di ottenere accesso alla tua macchina come root."
  Language
Dutch     -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"geeft aan dat iemand mogelijk roottoegang tot uw apparaat probeert te krijgen."
  Language
Ukrainian -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"вказує на те, що хтось може спробувати отримати доступ root до вашої машини."
  Language
Romanian  -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"indică că cineva are putea încerca să obțină acces root asupra mașinăria dumneavoastră."
  Language
Vietnamese -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"được xác định là có người đang có giành quyền truy cập vào root trên thiết bị của bạn."
  Language
Czech     -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"znamená, že se někdo možná pokouší získat přístup root k vašemu počítači."
  Language
Korean    -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"은(는) 누군가 컴퓨터에 대한 루트 액세스 권한을 얻으려고 할 수 있음을 나타냅니다."
  Language
_         -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"indicates that someone may be trying to gain root access to your machine."

security_5 :: PkgName -> Language -> Doc AnsiStyle
security_5 :: PkgName -> Language -> Doc AnsiStyle
security_5 (PkgName Text
p) = \case
  Language
Polish    -> Doc AnsiStyle
"UWAGA: PKGBUILD dla " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"zawiera wyrażenia bash znajdujące się na czarnej liście."
  Language
Arabic    -> Doc AnsiStyle
".في القائمة السودء bash في تعبيرات" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"باجل PKGBUILDتحذير: اﻟ"
  Language
Spanish   -> Doc AnsiStyle
"ADVERTENCIA: El PKGBUILD de" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"contiene expresiones bash en la lista negra."
  Language
Italian   -> Doc AnsiStyle
"ATTENZIONE: Il PKGBUILD di" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"contiene espressioni bash presenti nella lista nera."
  Language
Dutch     -> Doc AnsiStyle
"WAARSCHUWING: De PKGBUILD van" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"bevat bash-uitdrukkingen die op de zwarte lijst staan."
  Language
Ukrainian -> Doc AnsiStyle
"УВАГА! PKGBUILD пакунку" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"містить вирази bash, які занесені в чорний список."
  Language
Romanian  -> Doc AnsiStyle
"ATENȚIE! PKGBUILD-ul pachetului" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"conține expresii de bash pe lista neagră."
  Language
Vietnamese -> Doc AnsiStyle
"CẢNH BÁO: PKGBUILD của" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"chứa những câu lệnh bash nguy hiểm."
  Language
Czech     -> Doc AnsiStyle
"VAROVÁNÍ: PKGBUILD z" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"obsahuje zakazany bash výrazy"
  Language
Korean    -> Doc AnsiStyle
"경고: " Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"의 PKGBUILD에는 블랙리스트에 있는 bash 식이 포함되어 있습니다."
  Language
_         -> Doc AnsiStyle
"WARNING: The PKGBUILD of" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt Text
p Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"contains blacklisted bash expressions."

security_6 :: Language -> Doc AnsiStyle
security_6 :: Language -> Doc AnsiStyle
security_6 = \case
  Language
Polish     -> Doc AnsiStyle
"Czy chcesz zakończyć proces budowania?"
  Language
Arabic     -> Doc AnsiStyle
"هل تريد اقاف البناء؟"
  Language
Spanish    -> Doc AnsiStyle
"¿Desea salir del proceso de compilación?"
  Language
Italian    -> Doc AnsiStyle
"Terminare la compilazione?"
  Language
Dutch      -> Doc AnsiStyle
"Wilt u het bouwproces afbreken?"
  Language
Ukrainian  -> Doc AnsiStyle
"Бажаєте скасувати процес збірки?"
  Language
Romanian   -> Doc AnsiStyle
"Doriți anula procesul de compilare?"
  Language
Vietnamese -> Doc AnsiStyle
"Bạn có muốn dừng quá trình build?"
  Language
Czech      -> Doc AnsiStyle
"Přejete si ukončit build?"
  Language
Korean     -> Doc AnsiStyle
"빌드 프로세스를 종료하시겠습니까?"
  Language
_          -> Doc AnsiStyle
"Do you wish to quit the build process?"

security_7 :: Language -> Doc AnsiStyle
security_7 :: Language -> Doc AnsiStyle
security_7 = \case
  Language
Polish    -> Doc AnsiStyle
"Anulowano dalsze przetwarzanie by uniknąć egzekucji potencjalnie złośliwego kodu bash"
  Language
Arabic    -> Doc AnsiStyle
".الذي يحتمل أن يكون ضارا bash تم الغاء المعالجة الاضافيه لتجنب صدور"
  Language
Spanish   -> Doc AnsiStyle
"Se canceló el procesamiento posterior para evitar el código bash potencialmente malicioso."
  Language
Italian   -> Doc AnsiStyle
"Non saranno eseguite altre operazioni al fine di evitare l'esecuzione di codice bash potenzialmente malevolo."
  Language
Dutch     -> Doc AnsiStyle
"De verdere verwerking is afgebroken om het uitvoeren van potentieel schadelijke bash-code te voorkomen."
  Language
Ukrainian -> Doc AnsiStyle
"Подальша установка скасована, щоб уникнути потенційно шкідливого коду bash."
  Language
Romanian  -> Doc AnsiStyle
"S-a cancelat procesarea ulterioară pentru a evita cod de bash potențial rău intenționat."
  Language
Vietnamese -> Doc AnsiStyle
"Hãy dừng những quá trình tiếp theo để ngắn đoạn mã bash nguy hiểm."
  Language
Czech     -> Doc AnsiStyle
"Další proces byl zrušen, aby se zabránilo potenciálně škodlivému bash kódu."
  Language
Korean    -> Doc AnsiStyle
"잠재적으로 악의적인 bash 코드를 방지하기 위해 추가 처리가 취소되었습니다."
  Language
_         -> Doc AnsiStyle
"Cancelled further processing to avoid potentially malicious bash code."

security_8 :: Text -> Language -> Doc AnsiStyle
security_8 :: Text -> Language -> Doc AnsiStyle
security_8 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt -> Doc AnsiStyle
t) = \case
  Language
Polish    -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"jest komendą bash zawartą w polach tablicy twojego PKGBUILD."
  Language
Arabic    -> Doc AnsiStyle
".الخاص بك PKGBUILDمضمن بالحقول المصفوفة باﻟ bash امر" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
t
  Language
Spanish   -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"es un comando bash integrado en los campos de la matriz del PKGBUILD."
  Language
Italian   -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"è un comando bash presente all'interno degli array del tuo PKGBUILD."
  Language
Dutch     -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"is een bash-opdracht die is opgenomen in uw PKGBUILD-reeksvelden."
  Language
Ukrainian -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"- це команда bash, що вбудована в ваші поля масиву PKGBUILD"
  Language
Romanian  -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"este o comandă bash integrată în matricele din PKGBUILD."
  Language
Vietnamese -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"là lệnh bash được lồng trong mảng của PKGBUILD."
  Language
Czech     -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"je bash příkaz vložený do polí pole PKGBUILD."
  Language
Korean    -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"는 PKGBUILD 배열 필드에 표시된 bash 명령입니다."
  Language
_         -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"is a bash command inlined in your PKGBUILD array fields."

security_9 :: Text -> Language -> Doc AnsiStyle
security_9 :: Text -> Language -> Doc AnsiStyle
security_9 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt -> Doc AnsiStyle
t) = \case
  Language
Polish    -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"jest dziwną rzeczą w polach tablicy. Czy to bezpieczne?"
  Language
Arabic    -> Doc AnsiStyle
"شيء غريب ان يكون لديك في الحقول المصفوفة, هل هيا امن؟" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
t
  Language
Spanish   -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"es algo extraño para tener en sus campos de matriz. ¿Es seguro?"
  Language
Italian   -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"è una cosa strana da trovare all'interno degli array. E' sicura?"
  Language
Dutch     -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"is een vreemde eend in de bijt in uw reeksvelden. Is dit wel veilig?"
  Language
Ukrainian -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"- дивна річ в полях масиву. Це безпечно?"
  Language
Romanian  -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"e ciudat să se afle în matricele dumneavoastră. Asta este sigur?"
  Language
Vietnamese -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"là đoạn mã lạ trong mảng. Nó có an toàn không?"
  Language
Czech     -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"je zvláštní věc mít v polích. Je to bezpečné?"
  Language
Korean    -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"이것은 배열 안에서 볼 수 있는 이상한 것입니다. 안전합니까?"
  Language
_         -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"is a strange thing to have in your array fields. Is it safe?"

security_10 :: Text -> Language -> Doc AnsiStyle
security_10 :: Text -> Language -> Doc AnsiStyle
security_10 (Text -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt -> Doc AnsiStyle
t) = \case
  Language
Polish    -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"sugeruje, że ktoś próbował być sprytny używając zmiennych do ukrycia złośliwych komend."
  Language
Arabic    -> Doc AnsiStyle
".يعني ان شخصا ما كان يحاول ان يكون ذكيا مع المتغيرات لاخفاء الاوامر الخبيثة" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
t
  Language
Spanish   -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"implica que alguien estaba tratando de ser astuto con las variables para ocultar comandos maliciosos."
  Language
Italian   -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"implica che qualcuno stava trafficando con le variabili per nascondere comandi malevoli."
  Language
Dutch     -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"impliceert dat iemand op slinkse wijze probeerde om te gaan met variabelen om schadelijke opdrachten te verbergen."
  Language
Ukrainian -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"означає, що хтось намагається обдурити змінними, щоб сховати небеспечні команди."
  Language
Romanian  -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"implică că cineva încearcă să fie șmecher cu variabile pentru a ascunde comenzi rele intenționate."
  Language
Vietnamese -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"được xác định là có ai đó đang cố ẩn những câu lệnh nguy hiểm trong các biến."
  Language
Czech     -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"naznačuje že se někdo snažil být chytrý s proměnnými, aby skryl škodlivé příkazy."
  Language
Korean    -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"누군가 악의적인 명령을 숨기기 위해 변수를 교묘하게 다루려고 했다는 것을 암시합니다."
  Language
_         -> Doc AnsiStyle
t Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"implies that someone was trying to be clever with variables to hide malicious commands."

security_11 :: Language -> Doc AnsiStyle
security_11 :: Language -> Doc AnsiStyle
security_11 = \case
  Language
Polish    -> Doc AnsiStyle
"Ten PKGBUILD jest zbyt zawiły do odczytania - może ukrywać w sobie złośliwy kod."
  Language
Arabic    -> Doc AnsiStyle
".كان معقدا جدا للتحليل - يمكن ان يخفي برنامج ضار PKGBUILDذلك اﻟ"
  Language
Spanish   -> Doc AnsiStyle
"Éste PKGBUILD es demasiado complejo para analizar, puede estar ofuscando código malicioso."
  Language
Ukrainian -> Doc AnsiStyle
"Цей PKGBUILD був надто складним для аналізу - він може містити шкідливий код."
  Language
Romanian  -> Doc AnsiStyle
"Acel PKGBUILD este prea complicat de analizat - are putea ascunde cod rău intenționat."
  Language
Vietnamese -> Doc AnsiStyle
"Không thể đọc PKGBUILD - nó có thể chứa đoạn mã nguy hiểm."
  Language
Czech     -> Doc AnsiStyle
"Tento PKGBUILD je příliš složitý na to, aby jej bylo možné analyzovat/rezebrat – může obsahovat matoucí škodlivý kód."
  Language
Korean    -> Doc AnsiStyle
"이 PKGBUILD는 분석하기에 너무 복잡합니다 - 악성코드를 난독화하고 있을 수 있습니다."
  Language
Dutch      -> Doc AnsiStyle
"Deze PKGBUILD is te complex om te verwerken. Het bestand bevat mogelijk verborgen schadelijke code."
  Language
_         -> Doc AnsiStyle
"That PKGBUILD is too complex to parse - it may be obfuscating malicious code."

security_12 :: Language -> Doc AnsiStyle
security_12 :: Language -> Doc AnsiStyle
security_12 = \case
  Language
Polish     -> Doc AnsiStyle
"Potencjalne luki w bezpieczeństwie wykryte w PKGBUILD"
  Language
Arabic     -> Doc AnsiStyle
".PKGBUILDاحتمال وجود ثغرات امنية في اﻟ"
  Language
Spanish    -> Doc AnsiStyle
"Posibles vulnerabilidades de PKGBUILD detectadas."
  Language
Ukrainian  -> Doc AnsiStyle
"Потенційні вразливості знайдено в PKGBUILD."
  Language
Romanian   -> Doc AnsiStyle
"Vulnerabilități potențiale detectate în PKGBUILD."
  Language
Vietnamese -> Doc AnsiStyle
"Phát hiện lỗ hổng trong PKGBUILD."
  Language
Czech      -> Doc AnsiStyle
"Byla zjištěna potenciální bezpečnostní chyba v PKGBUILD."
  Language
Korean     -> Doc AnsiStyle
"잠재적인 PKGBUILD 취약점 발견됨."
  Language
Dutch      -> Doc AnsiStyle
"Er zijn mogelijke kwetsbaarheden aangetroffen in het PKGBUILD-bestand."
  Language
_          -> Doc AnsiStyle
"Potential PKGBUILD vulnerabilities detected."

security_13 :: Word -> Language -> Doc AnsiStyle
security_13 :: Word -> Language -> Doc AnsiStyle
security_13 (Word -> Doc AnsiStyle
forall a. Pretty a => a -> Doc AnsiStyle
bt -> Doc AnsiStyle
w) = \case
  Language
Polish    -> Doc AnsiStyle
"Sprawdzanie PKGBUILD" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
w Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"w poszukiwaniu luk w bezpieczeństwie..."
  Language
Arabic    -> Doc AnsiStyle
"...بحثا عن نقاط ضعف" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
w Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"تبع PKGBUILDتحقق اﻟ"
  Language
Spanish   -> Doc AnsiStyle
"Comprobando" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
w Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"PKGBUILDs por vulnerabilidades..."
  Language
Ukrainian -> Doc AnsiStyle
"Перевіряємо" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
w Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"PKGBUILD-ів на вразливості..."
  Language
Romanian  -> Doc AnsiStyle
"Se verifică PKGBUILD-uri" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
w Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"pentru vulnerabilități..."
  Language
Vietnamese -> Doc AnsiStyle
"Tìm kiếm" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
w Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"lỗ hổng trong PKGBUILD..."
  Language
Czech     -> Doc AnsiStyle
"Kontrola bezpečnostních chyb v" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
w Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"PKGBUILD"
  Language
Korean    -> Doc AnsiStyle
w Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"PKGBUILD 취약점 확인 중..."
  Language
Dutch      -> Doc AnsiStyle
"Bezig met controleren van" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
w Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"PKGBUILDs op kwetsbaarheden…"
  Language
_         -> Doc AnsiStyle
"Checking" Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
w Doc AnsiStyle -> Doc AnsiStyle -> Doc AnsiStyle
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc AnsiStyle
"PKGBUILDs for vulnerabilities..."

security_14 :: Language -> Doc AnsiStyle
security_14 :: Language -> Doc AnsiStyle
security_14 = \case
  Language
Polish     -> Doc AnsiStyle
"Nie wykryto żadnych luk w bezpieczeństwie."
  Language
Arabic     -> Doc AnsiStyle
".لا تم العثور على نقاط ضعف"
  Language
Spanish    -> Doc AnsiStyle
"No se detectaron vulnerabilidades."
  Language
Ukrainian  -> Doc AnsiStyle
"Ніяких вразливостей не було знайдено."
  Language
Romanian   -> Doc AnsiStyle
"Nu s-a găsit nici o vulnerabilitate."
  Language
Vietnamese -> Doc AnsiStyle
"Không tìm thấy lỗ hổng."
  Language
Czech      -> Doc AnsiStyle
"Nebyly nalezeny žádné bezpečnostní chyby."
  Language
Korean     -> Doc AnsiStyle
"발견된 취약점이 없습니다."
  Language
Dutch      -> Doc AnsiStyle
"Er zijn geen kwetsbaarheden aangetroffen."
  Language
_          -> Doc AnsiStyle
"No vulnerabilities detected."

-----------------------
-- Aura/Utils functions
-----------------------
yesNoMessage :: Language -> Doc ann
yesNoMessage :: Language -> Doc ann
yesNoMessage = \case
    Language
Polish     -> Doc ann
"[T/n]"
    Language
Arabic     -> Doc ann
"[ن/لا]"
    Language
Turkish    -> Doc ann
"[e/h]"
    Language
Croatian   -> Doc ann
"[D/n]"
    Language
German     -> Doc ann
"[J/n]"
    Language
Spanish    -> Doc ann
"[S/n]"
    Language
Norwegian  -> Doc ann
"[J/n]"
    Language
Italian    -> Doc ann
"[S/n]"
    Language
Portuguese -> Doc ann
"[S/n]"
    Language
French     -> Doc ann
"[O/n]"
    Language
Russian    -> Doc ann
"[Д/н]"
    Language
Esperanto  -> Doc ann
"[J/n]"
    Language
Dutch      -> Doc ann
"[J/n]"
    Language
Ukrainian  -> Doc ann
"[Т/н]"
    Language
Romanian   -> Doc ann
"[D/n]"
    Language
Czech      -> Doc ann
"[A,n]"
    Language
_          -> Doc ann
"[Y/n]"

yesPattern :: Language -> [T.Text]
yesPattern :: Language -> [Text]
yesPattern Language
lang = (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Text
T.toCaseFold ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ case Language
lang of
    Language
Polish     -> [Text
"t", Text
"tak"]
    Language
Arabic     -> [Text
"ن", Text
"نعم"]
    Language
Turkish    -> [Text
"e", Text
"evet"]
    Language
Croatian   -> [Text
"d", Text
"da"]
    Language
German     -> [Text
"j", Text
"ja"]
    Language
Spanish    -> [Text
"s", Text
"si"]
    Language
Norwegian  -> [Text
"j", Text
"ja"]
    Language
Italian    -> [Text
"s", Text
"si"]
    Language
Portuguese -> [Text
"s", Text
"sim"]
    Language
French     -> [Text
"o", Text
"oui"]
    Language
Russian    -> [Text
"д", Text
"да"]
    Language
Esperanto  -> [Text
"j", Text
"jes"]
    Language
Dutch      -> [Text
"j", Text
"ja"]
    Language
Ukrainian  -> [Text
"т", Text
"так"]
    Language
Romanian   -> [Text
"d", Text
"da"]
    Language
Czech      -> [Text
"a", Text
"ano"]
    Language
_          -> [Text
"y", Text
"yes"]

----------------------
-- Pluralization rules
----------------------
pluralRussian :: Integral n => a -> a -> a -> n -> a
pluralRussian :: a -> a -> a -> n -> a
pluralRussian a
singular a
plural1 a
plural2 n
n | n
n n -> n -> Ratio n
forall a. Integral a => a -> a -> Ratio a
% n
10 Ratio n -> Ratio n -> Bool
forall a. Eq a => a -> a -> Bool
== Ratio n
1 Bool -> Bool -> Bool
&& n
n n -> n -> Ratio n
forall a. Integral a => a -> a -> Ratio a
% n
100 Ratio n -> Ratio n -> Bool
forall a. Eq a => a -> a -> Bool
/= Ratio n
11 = a
singular
                                         | n
n n -> n -> Ratio n
forall a. Integral a => a -> a -> Ratio a
% n
10 Ratio n -> [Ratio n] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Ratio n
2, Ratio n
3, Ratio n
4] = a
plural1
                                         | Bool
otherwise = a
plural2