]> Git — Sourcephile - comptalang.git/blob - cli/Hcompta/CLI/Lang.hs
Ajout : CLI.Lang : traductions.
[comptalang.git] / cli / Hcompta / CLI / Lang.hs
1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE MultiParamTypeClasses #-}
4 {-# LANGUAGE OverloadedStrings #-}
5 {-# LANGUAGE TupleSections #-}
6 {-# OPTIONS_GHC -fno-warn-orphans #-}
7 module Hcompta.CLI.Lang where
8
9 import Control.Monad (liftM)
10 import qualified Data.List
11 import Data.Maybe (catMaybes, fromMaybe)
12 import qualified Data.Text
13 import Data.Text (Text)
14 import qualified Data.Text.Lazy as TL
15 import Prelude hiding (error)
16 import System.Environment (getEnvironment)
17 import System.IO.Memoize (once)
18 import qualified Text.Parsec as Parsec
19 import qualified Text.Parsec.Error as Parsec.Error
20
21 import qualified Hcompta.Account as Account
22 import Hcompta.Amount (Amount)
23 import Hcompta.Amount.Unit (Unit)
24 import qualified Hcompta.Amount.Write as Amount.Write
25 import Hcompta.Date (Date)
26 import qualified Hcompta.Date.Read as Date.Read
27 import qualified Hcompta.Date.Write as Date.Write
28 import qualified Hcompta.Filter.Read as Filter.Read
29 import Hcompta.Lib.Leijen (ToDoc(..), (<>))
30 import qualified Hcompta.Lib.Leijen as W
31 import qualified Hcompta.Lib.Parsec as Lib.Parsec
32
33 -- * Type 'Lang'
34 data Lang
35 = EN
36 | FR
37 deriving (Show)
38
39 -- * Class 'Translate'
40 class Translate from to where
41 translate :: Lang -> from -> to
42 instance Translate e e where
43 translate _lang = id
44
45 -- TODO: check that this is expected behavior
46 -- and portability issues
47 from_Env :: IO Lang
48 from_Env = do
49 once getEnvironment
50 >>= liftM (\env ->
51 fromMaybe EN $ from_Strings $
52 Data.List.concatMap
53 ((\lang ->
54 let short = takeWhile (/= '_') lang in
55 if short == lang
56 then [lang]
57 else [lang, short])
58 . Data.List.takeWhile (/= '.') ) $
59 catMaybes
60 [ Data.List.lookup "LC_ALL" env
61 , Data.List.lookup "LC_CTYPE" env
62 , Data.List.lookup "LANG" env
63 ])
64
65 from_Strings :: [String] -> Maybe Lang
66 from_Strings s =
67 case s of
68 ("fr" :_) -> Just FR
69 ("fr_FR":_) -> Just FR
70 ("en" :_) -> Just EN
71 ("en_US":_) -> Just EN
72 (_:xs) -> from_Strings xs
73 [] -> Nothing
74
75 (#) :: ToDoc () a => a -> W.Doc
76 (#) = toDoc ()
77
78 instance ToDoc () Text where
79 toDoc _ = W.strict_text
80 instance ToDoc () String where
81 toDoc _ = W.strict_text . Data.Text.pack
82 instance ToDoc () Int where
83 toDoc _ = W.int
84 instance ToDoc () Integer where
85 toDoc _ = W.integer
86 instance ToDoc () Unit where
87 toDoc _ = Amount.Write.unit
88 instance ToDoc () Amount where
89 toDoc _ = Amount.Write.amount
90 instance ToDoc Lang Date where
91 toDoc _ = Date.Write.date
92 instance ToDoc Lang Date.Read.Error where
93 toDoc FR e =
94 case e of
95 Date.Read.Error_year_or_day_is_missing ->
96 "l’année ou le jour est manquant·e"
97 Date.Read.Error_invalid_date (year, month, day) ->
98 "date incorrecte (année " <> (#)year <> ", mois " <> (#)month <> ", jour " <> (#)day <> ")"
99 Date.Read.Error_invalid_time_of_day (hour, minute, second) ->
100 "heure incorrecte (heure " <> (#)hour <> ", minute " <> (#)minute <> ", seconde " <> (#)second <> ")"
101 toDoc EN e =
102 case e of
103 Date.Read.Error_year_or_day_is_missing ->
104 "year or day is missing"
105 Date.Read.Error_invalid_date (year, month, day) ->
106 "invalid date (year " <> (#)year <> ", month " <> (#)month <> ", day " <> (#)day <> ")"
107 Date.Read.Error_invalid_time_of_day (hour, minute, second) ->
108 "invalid time of day (hour " <> (#)hour <> ", minute " <> (#)minute <> ", second " <> (#)second <> ")"
109 instance Translate Filter.Read.Error W.Doc where
110 translate lang@FR err =
111 case err of
112 Filter.Read.Error_Unknown -> "erreur"
113 Filter.Read.Error_Filter_Date d -> toDoc lang d
114 Filter.Read.Error_Filter_Date_Interval (l, h) ->
115 "mauvais intervalle: (" <> toDoc () l <> ", " <> toDoc () h <> ")"
116 translate lang@EN err =
117 case err of
118 Filter.Read.Error_Unknown -> "error"
119 Filter.Read.Error_Filter_Date d -> toDoc lang d
120 Filter.Read.Error_Filter_Date_Interval (l, h) ->
121 "wrong interval: (" <> toDoc () l <> ", " <> toDoc () h <> ")"
122
123 -- * Type 'Account'
124 data Account
125 = Account_Equilibrium
126 instance Translate Account Account.Account where
127 translate EN t =
128 case t of
129 Account_Equilibrium -> Account.account "Equilibrium" []
130 translate FR t =
131 case t of
132 Account_Equilibrium -> Account.account "Équilibre" []
133
134 -- * Type 'Comment'
135 data Comment
136 = Comment_Equilibrium
137 instance Translate Comment Text where
138 translate EN t =
139 case t of
140 Comment_Equilibrium -> "Equilibrium posting"
141 translate FR t =
142 case t of
143 Comment_Equilibrium -> "Mouvement d’équilibre"
144
145 -- * Type 'Description'
146 data Description
147 = Description_Exercise Exercise_OC
148 data Exercise_OC
149 = Exercise_Opening
150 | Exercise_Closing
151 deriving (Eq, Show)
152
153 instance Translate Description Text where
154 translate EN t =
155 case t of
156 Description_Exercise oc ->
157 case oc of
158 Exercise_Opening -> "Opening balance"
159 Exercise_Closing -> "Closing balance"
160 translate FR t =
161 case t of
162 Description_Exercise oc ->
163 case oc of
164 Exercise_Opening -> "Solde d’ouverture"
165 Exercise_Closing -> "Solde de fermeture"
166
167 -- * Type 'Error'
168 data Error
169 = Error_Failed_to_include_file FilePath
170 | Error_Failed_to_read_file FilePath
171 | Error_No_input_file_given
172 | Error_One_command_is_required
173 | Error_Option_Balance_Format
174 | Error_Option_Balance_Heritage
175 | Error_Option_Balance_Redundant
176 | Error_Option_Balance_Total
177 | Error_Option_Color
178 | Error_Option_Equilibrium
179 | Error_Option_Equilibrium_Credit
180 | Error_Option_Equilibrium_Debit
181 | Error_Option_Tags_Tree
182 | Error_Option_Verbosity
183 | Error_Transaction_Invalid_date Integer Int Int
184 | Error_Transaction_Invalid_time_of_day Int Int Integer
185 | Error_Transaction_The_following_transaction_is_not_equilibrated_because
186 | Error_Transaction_The_following_virtual_transaction_is_not_equilibrated_because
187 | Error_Transaction_Unit_sums_up_to_the_non_null_amount Unit Amount
188 | Error_Transaction_Year_or_day_is_missing
189 | Error_Unkown_command String
190 instance Translate Error W.Doc where
191 translate EN t =
192 case t of
193 Error_Failed_to_read_file path -> "failed to read file: " <> (#)path
194 Error_Failed_to_include_file path -> "failed to include file: " <> (#)path
195 Error_No_input_file_given ->
196 W.vsep
197 [ "no input file given, please use:"
198 , "- either -i FILE_OF_JOURNAL parameter"
199 , "- or LEDGER_FILE environment variable."
200 ]
201 Error_One_command_is_required -> "a COMMAND is required"
202 Error_Option_Balance_Format -> "--format option expects \"close\", \"open\", or \"table\" as argument"
203 Error_Option_Balance_Heritage -> "--heritage option expects \"yes\" or \"no\" as argument"
204 Error_Option_Balance_Redundant -> "--redundant option expects \"yes\" or \"no\" as argument"
205 Error_Option_Balance_Total -> "--total option expects \"yes\" or \"no\" as argument"
206 Error_Option_Color -> "--color option expects \"auto\" (default), \"yes\" or \"no\" as argument"
207 Error_Option_Equilibrium -> "--eq option expects an ACCOUNT"
208 Error_Option_Equilibrium_Credit -> "--eq-credit option expects an ACCOUNT"
209 Error_Option_Equilibrium_Debit -> "--eq-debit option expects an ACCOUNT"
210 Error_Option_Tags_Tree -> "--tree option expects \"yes\" or \"no\" as value"
211 Error_Option_Verbosity -> "--verbosity option expects \"error\", \"warn\", \"info\" or \"debug\" as argument"
212 Error_Transaction_Invalid_date year month dom ->
213 "invalid date (year " <> (#)year <> ", month " <> (#)month <> ", day " <> (#)dom <> ")"
214 Error_Transaction_Invalid_time_of_day hour minute second ->
215 "invalid time of day (hour " <> (#)hour <> ", minute " <> (#)minute <> ", second " <> (#)second <> ")"
216 Error_Transaction_The_following_transaction_is_not_equilibrated_because ->
217 "the following transaction is not equilibrated, because:"
218 Error_Transaction_The_following_virtual_transaction_is_not_equilibrated_because ->
219 "the following virtual transaction is not equilibrated, because:"
220 Error_Transaction_Unit_sums_up_to_the_non_null_amount unit amount ->
221 " - unit " <> (#)unit <> " sums up to the non-null amount: " <> (#)amount
222 Error_Transaction_Year_or_day_is_missing ->
223 "year or day is missing"
224 Error_Unkown_command cmd -> "unkown command: " <> (#)cmd
225 translate FR t =
226 case t of
227 Error_Failed_to_read_file path -> "échec de la lecture du fichier : " <> (#)path
228 Error_Failed_to_include_file path -> "échec à l’inclusion du fichier : " <> (#)path
229 Error_No_input_file_given ->
230 W.vsep
231 [ "aucun fichier d’entrée indiqué, veuillez utiliser :"
232 , " - soit le paramètre -i FICHIER_DE_JOURNAL,"
233 , " - soit la variable d’environnement LEDGER_FILE."
234 ]
235 Error_One_command_is_required -> "une COMMANDE est requise"
236 Error_Option_Balance_Format -> "le paramètre --format s’attend à \"close\", \"open\" ou \"table\" comme argument"
237 Error_Option_Balance_Heritage -> "le paramètre --heritage s’attend à \"yes\" ou \"no\" comme argument"
238 Error_Option_Balance_Redundant -> "le paramètre --redundant s’attend à \"yes\" ou \"no\" comme argument"
239 Error_Option_Balance_Total -> "le paramètre --total s’attend à \"yes\" ou \"no\" comme argument"
240 Error_Option_Color -> "le paramètre --color s’attend à \"auto\" (défaut), \"yes\" ou \"no\" comme argument"
241 Error_Option_Equilibrium -> "le paramètre --eq s’attend à un COMPTE"
242 Error_Option_Equilibrium_Credit -> "le paramètre --eq-credit s’attend à un COMPTE"
243 Error_Option_Equilibrium_Debit -> "le paramètre --eq-debit s’attend à un COMPTE"
244 Error_Option_Tags_Tree -> "le paramètre --total s’attend à \"yes\" ou \"no\" comme argument"
245 Error_Option_Verbosity -> "le paramètre --verbosity s’attend à \"error\", \"warn\", \"info\", or \"debug\" comme argument"
246 Error_Transaction_Invalid_date year month dom ->
247 "date incorrecte (année " <> (#)year <> ", mois " <> (#)month <> ", jour " <> (#)dom <> ")"
248 Error_Transaction_Invalid_time_of_day hour minute second ->
249 "heure incorrecte (heure " <> (#)hour <> ", minute " <> (#)minute <> ", seconde " <> (#)second <> ")"
250 Error_Transaction_The_following_transaction_is_not_equilibrated_because ->
251 "la transaction suivante n’est pas équilibrée, car :"
252 Error_Transaction_The_following_virtual_transaction_is_not_equilibrated_because ->
253 "la transaction virtuelle suivante n’est pas équilibrée, car :"
254 Error_Transaction_Unit_sums_up_to_the_non_null_amount unit amount ->
255 " - l’unité " <> (#)unit <> " a le solde non-nul : " <> (#)amount
256 Error_Transaction_Year_or_day_is_missing ->
257 "l’année ou le jour est manquant-e"
258 Error_Unkown_command cmd -> "commande inconnue : " <> (#)cmd
259
260 -- * Type 'Error_Parsec'
261 data Error_Parsec
262 = Error_Parsec_Expect W.Doc
263 | Error_Parsec_Message String
264 | Error_Parsec_Or
265 | Error_Parsec_Sysunexpect String
266 | Error_Parsec_Sysunexpect_EOI
267 | Error_Parsec_Unexpect W.Doc
268 | Error_Parsec_Unknown
269 instance ToDoc Lang Error_Parsec where
270 toDoc EN t =
271 case t of
272 Error_Parsec_Expect doc -> "but expect : " <> (#)doc
273 Error_Parsec_Message doc -> (#)doc
274 Error_Parsec_Or -> "or"
275 Error_Parsec_Sysunexpect doc -> "is written : " <> (#)doc
276 Error_Parsec_Sysunexpect_EOI -> "end of file unexpected"
277 Error_Parsec_Unexpect doc -> "found : " <> (#)doc
278 Error_Parsec_Unknown -> "unkown"
279 toDoc FR t =
280 case t of
281 Error_Parsec_Expect doc -> "mais s’attend à : " <> (#)doc
282 Error_Parsec_Message doc -> (#)doc
283 Error_Parsec_Or -> "ou"
284 Error_Parsec_Sysunexpect doc -> "est écrit : " <> (#)doc
285 Error_Parsec_Sysunexpect_EOI -> "fin de fichier inattendue"
286 Error_Parsec_Unexpect doc -> "trouve : " <> (#)doc
287 Error_Parsec_Unknown -> "inconnu"
288 instance Translate Parsec.SourcePos W.Doc where
289 translate EN pos = do
290 let line = Parsec.sourceLine pos
291 let col = Parsec.sourceColumn pos
292 case Parsec.sourceName pos of
293 "" -> "(line " <> (#)line <> ", column " <> (#)col <> ")"
294 path -> "(line " <> (#)line <> ", column " <> (#)col <> ") in: " <> (#)path
295 translate FR pos = do
296 let line = Parsec.sourceLine pos
297 let col = Parsec.sourceColumn pos
298 case Parsec.sourceName pos of
299 "" -> "(ligne " <> (#)line <> ", colonne " <> (#)col <> ")"
300 path -> "(ligne " <> (#)line <> ", colonne " <> (#)col <> ") dans : " <> (#)path
301 instance Translate e W.Doc
302 => Translate [Lib.Parsec.Error e] W.Doc where
303 translate lang errors =
304 W.vsep $ do
305 (flip map) errors $ (\error ->
306 case error of
307 Lib.Parsec.Error_At pos errs -> W.vsep $
308 [ translate lang pos
309 , translate lang errs
310 ]
311 Lib.Parsec.Error_Parser err ->
312 W.vsep $
313 [ translate lang (Parsec.errorPos err)
314 , showErrorMessages
315 (Parsec.Error.errorMessages err)
316 ]
317 Lib.Parsec.Error_Custom pos err -> W.vsep $
318 [ translate lang pos
319 , translate lang err
320 ]
321 )
322 where
323 showErrorMessages :: [Parsec.Error.Message] -> W.Doc
324 showErrorMessages msgs
325 | null msgs = toDoc lang $ Error_Parsec_Unknown
326 | otherwise = W.vsep $ -- clean $
327 [showSysUnExpect, showUnExpect, showExpect, showMessages]
328 where
329 (sysUnExpect,msgs1) = span ((Parsec.Error.SysUnExpect "") ==) msgs
330 (unExpect,msgs2) = span ((Parsec.Error.UnExpect "") ==) msgs1
331 (expect,messages) = span ((Parsec.Error.Expect "") ==) msgs2
332
333 showExpect = showMany (Just (toDoc lang . Error_Parsec_Expect)) expect
334 showUnExpect = showMany (Just (toDoc lang . Error_Parsec_Unexpect)) unExpect
335 showSysUnExpect
336 | not (null unExpect) || null sysUnExpect = W.empty
337 | null firstMsg = toDoc lang $ Error_Parsec_Sysunexpect_EOI
338 | otherwise = toDoc lang $ Error_Parsec_Sysunexpect firstMsg
339 where
340 firstMsg = Parsec.Error.messageString (head sysUnExpect)
341
342 showMessages = showMany Nothing messages
343
344 -- helpers
345 showMany :: (Maybe (W.Doc -> W.Doc)) -> [Parsec.Error.Message] -> W.Doc
346 showMany pre msgs_ =
347 case clean (map Parsec.Error.messageString msgs_) of
348 [] -> W.empty
349 ms ->
350 case pre of
351 Nothing -> commasOr ms
352 Just p -> p $ commasOr ms
353
354 commasOr :: [String] -> W.Doc
355 commasOr [] = W.empty
356 commasOr [m] = W.bold $ W.dullblack $ W.text $ TL.pack m
357 commasOr ms = commaSep (init ms)
358 <> (W.space <> toDoc lang Error_Parsec_Or <> W.space)
359 <> (W.bold $ W.dullblack $ W.text $ TL.pack $ last ms)
360 commaSep = W.intercalate (W.comma <> W.space)
361 (W.bold . W.dullblack . W.text . TL.pack)
362 . clean
363
364 clean = Data.List.nub . filter (not . null)
365
366 -- * Type 'Header'
367 data Header
368 = Header_Accounts
369 | Header_Accounts_Depth
370 | Header_Journals
371 | Header_Tags
372 | Header_Tags_Distinct
373 | Header_Transactions
374 | Header_Transactions_Date
375 | Header_Units
376 instance Translate Header [Text] where
377 translate EN t =
378 case t of
379 Header_Accounts -> ["Accounts"]
380 Header_Accounts_Depth -> ["Accounts","Depth"]
381 Header_Journals -> ["Journals"]
382 Header_Tags -> ["Tags"]
383 Header_Tags_Distinct -> ["Tags", "Distinct"]
384 Header_Transactions -> ["Transactions"]
385 Header_Transactions_Date -> ["Transactions", "Date"]
386 Header_Units -> ["Unit"]
387 translate FR t =
388 case t of
389 Header_Accounts -> ["Comptes"]
390 Header_Accounts_Depth -> ["Comptes","Profondeur"]
391 Header_Journals -> ["Journaux"]
392 Header_Tags -> ["Tags"]
393 Header_Tags_Distinct -> ["Tags", "Distincts"]
394 Header_Transactions -> ["Écritures"]
395 Header_Transactions_Date -> ["Écritures", "Date"]
396 Header_Units -> ["Unités"]
397
398 -- * Type 'Help'
399 data Help
400 = Help_Command_Balance
401 | Help_Command_General_Ledger
402 | Help_Command_Journal
403 | Help_Command_Journals
404 | Help_Command_Stats
405 | Help_Command_Tags
406 | Help_Option_Balance_Format
407 | Help_Option_Balance_Heritage
408 | Help_Option_Balance_Redundant
409 | Help_Option_Balance_Total
410 | Help_Option_Color
411 | Help_Option_Equilibrium
412 | Help_Option_Equilibrium_Credit
413 | Help_Option_Equilibrium_Debit
414 | Help_Option_Filter_Balance
415 | Help_Option_Filter_General_Ledger
416 | Help_Option_Filter_Posting
417 | Help_Option_Filter_Tag
418 | Help_Option_Filter_Transaction
419 | Help_Option_Help
420 | Help_Option_Input
421 | Help_Option_Lang
422 | Help_Option_Output
423 | Help_Option_Overwrite
424 | Help_Option_Tags_Tree
425 | Help_Option_Verbosity
426 | Help_Synopsis
427 instance Translate Help String where
428 translate EN t =
429 case t of
430 Help_Command_Balance -> "List final DEBITs, CREDITs and BALANCEs of ACCOUNTs"
431 Help_Command_General_Ledger -> "List DEBITs, CREDITs and BALANCEs of ACCOUNTs after each TRANSACTION"
432 Help_Command_Journal -> "List TRANSACTIONs"
433 Help_Command_Journals -> "List JOURNAL FILEs"
434 Help_Command_Stats -> "Show some statistics"
435 Help_Command_Tags -> "List TAGs"
436 Help_Option_Balance_Format -> "Select BALANCE output format"
437 Help_Option_Balance_Heritage -> "Propagate AMOUNTs to ascending ACCOUNTs"
438 Help_Option_Balance_Redundant -> "Also show ACCOUNTs with null AMOUNT or the same AMOUNTs than its descending ACCOUNT"
439 Help_Option_Balance_Total -> "Show transversal DEBIT, CREDIT, and BALANCE by UNIT"
440 Help_Option_Color -> "Colorize output"
441 Help_Option_Equilibrium -> "Specify the ACCOUNT equilibrating an opening or closing BALANCE"
442 Help_Option_Equilibrium_Credit -> "Like --eq but only when the AMOUNT is a CREDIT"
443 Help_Option_Equilibrium_Debit -> "Like --eq but only when the AMOUNT is a DEBIT"
444 Help_Option_Filter_Balance -> "Apply given FILTER_OF_BALANCE, multiple uses are joined with a logical AND"
445 Help_Option_Filter_General_Ledger -> "Apply given FILTER_OF_GENERAL_LEDGER, multiple uses are joined with a logical AND"
446 Help_Option_Filter_Posting -> "Apply given FILTER_OF_POSTING, multiple uses are joined with a logical AND"
447 Help_Option_Filter_Tag -> "Apply given FILTER_OF_TAG, multiple uses are joined with a logical AND"
448 Help_Option_Filter_Transaction -> "Apply given FILTER_OF_TRANSACTION, multiple uses are joined with a logical AND"
449 Help_Option_Help -> "Show this help"
450 Help_Option_Input -> "Read a JOURNAL from given FILE, multiple uses merge the data"
451 Help_Option_Lang -> "RFC1766 / ISO 639-1 language code (fr, en-GB, etc.)"
452 Help_Option_Output -> "Append output data to given FILE, multiple uses output to multiple FILEs"
453 Help_Option_Overwrite -> "Overwrite given FILE with output data, multiple uses overwrite to multiple FILEs"
454 Help_Option_Tags_Tree -> "Show TAGs as a tree"
455 Help_Option_Verbosity -> "Set verbosity level, or increment it when used multiple times"
456 Help_Synopsis -> "[OPTIONS] COMMAND [COMMAND_OPTIONS]"
457 translate FR t =
458 case t of
459 Help_Command_Balance -> "Liste les DÉBITs, CRÉDITs et SOLDEs finaux des COMPTEs"
460 Help_Command_General_Ledger -> "Liste les DÉBITs, CRÉDITs et SOLDEs des COMPTEs après chaque ÉCRITURE"
461 Help_Command_Journal -> "Liste les ÉCRITUREs"
462 Help_Command_Journals -> "Liste les FICHIERs des JOURNAUX"
463 Help_Command_Stats -> "Affiche quelques statistiques"
464 Help_Command_Tags -> "Liste les TAGs"
465 Help_Option_Balance_Format -> "Sélectionne le format de BALANCE en sortie"
466 Help_Option_Balance_Heritage -> "Propage les MONTANTs aux COMPTEs ascendants"
467 Help_Option_Balance_Redundant -> "Affiche également les COMPTEs dont le MONTANT est nul ou qui ont les mêmes MONTANTs que leur COMPTE descendant"
468 Help_Option_Balance_Total -> "Affiche les SOLDEs transversaux par UNITÉ"
469 Help_Option_Color -> "Colore la sortie"
470 Help_Option_Equilibrium -> "Indique le COMPTE d’équilibre pour une BALANCE d’ouverture ou de fermeture"
471 Help_Option_Equilibrium_Credit -> "Comme --eq mais seulement lorsque le MONTANT est un CRÉDIT"
472 Help_Option_Equilibrium_Debit -> "Comme --eq mais seulement lorsque le MONTANT est un DÉBIT"
473 Help_Option_Filter_Balance -> "Applique le FILTRE_DE_BALANCE donné, un usage multiple agit comme un ET logique"
474 Help_Option_Filter_General_Ledger -> "Applique le FILTRE_DE_GRAND_LIVRE donné, un usage multiple agit comme un ET logique"
475 Help_Option_Filter_Posting -> "Applique le FILTRE_DE_MOUVEMENT donné, un usage multiple agit comme un ET logique"
476 Help_Option_Filter_Tag -> "Applique le FILTRE_DE_TAG donné, un usage multiple agit comme un ET logique"
477 Help_Option_Filter_Transaction -> "Applique le FILTRE_D’ÉCRITURE donné, un usage multiple agit comme un ET logique"
478 Help_Option_Help -> "Affiche cette aide"
479 Help_Option_Input -> "Lit un JOURNAL dans le FICHIER donné, un usage multiple fusionne les données"
480 Help_Option_Lang -> "Code de langue RFC1766 / ISO 639-1 language code (fr, en-GB, etc.)"
481 Help_Option_Output -> "Ajoute la sortie au FICHIER donné, un usage multiple écrit dans plusieurs FICHIERs"
482 Help_Option_Overwrite -> "Écrase le FICHIER donné avec la sortie, un usage multiple écrase plusieurs FICHIERs"
483 Help_Option_Tags_Tree -> "Affiche les TAGs en arborescence"
484 Help_Option_Verbosity -> "Indique le niveau de verbosité, ou l’incrémente lorsque utilisé plusieurs fois"
485 Help_Synopsis -> "[PARAMÈTRES] COMMANDE [PARAMÈTRES_DE_COMMANDE]"
486
487 -- * Type 'Section'
488 data Section
489 = Section_Commands
490 | Section_Description
491 | Section_Syntax
492 | Section_Options
493 deriving (Eq, Show)
494 instance Translate Section String where
495 translate EN t =
496 case t of
497 Section_Commands -> "COMMANDS (use COMMAND --help for help on COMMAND)"
498 Section_Description -> "DESCRIPTION"
499 Section_Syntax -> "SYNTAX"
500 Section_Options -> "OPTIONS"
501 translate FR t =
502 case t of
503 Section_Commands -> "COMMANDES (utilisez COMMANDE --help pour une aide sur COMMANDE)"
504 Section_Description -> "DESCRIPTION"
505 Section_Syntax -> "SYNTAXE"
506 Section_Options -> "PARAMÈTRES"
507
508 -- * Type 'Title'
509 data Title
510 = Title_Account
511 | Title_Balance
512 | Title_Credit
513 | Title_Date
514 | Title_Debit
515 | Title_Description
516 | Title_Running_balance
517 | Title_Running_credit
518 | Title_Running_debit
519 instance Translate Title Text where
520 translate EN t =
521 case t of
522 Title_Account -> "Account"
523 Title_Balance -> "Balance"
524 Title_Credit -> "Credit"
525 Title_Date -> "Date"
526 Title_Debit -> "Debit"
527 Title_Description -> "Wording"
528 Title_Running_balance -> "Running balance"
529 Title_Running_credit -> "Running credit"
530 Title_Running_debit -> "Running debit"
531 translate FR t =
532 case t of
533 Title_Account -> "Compte"
534 Title_Balance -> "Solde"
535 Title_Credit -> "Crédit"
536 Title_Date -> "Date"
537 Title_Debit -> "Débit"
538 Title_Description -> "Libellé"
539 Title_Running_balance -> "Solde cumulé"
540 Title_Running_credit -> "Crédit cumulé"
541 Title_Running_debit -> "Débit cumulé"
542
543 -- * Type 'Type'
544 data Type
545 = Type_Account
546 | Type_File
547 | Type_File_Journal
548 | Type_Filter_Balance
549 | Type_Filter_General_Ledger
550 | Type_Filter_Posting
551 | Type_Filter_Tag
552 | Type_Filter_Transaction
553 | Type_Option
554 deriving (Eq, Show)
555 instance Translate Type String where
556 translate EN t =
557 case t of
558 Type_Account -> "ACCOUNT"
559 Type_File -> "FILE"
560 Type_File_Journal -> "FILE_OF_JOURNAL"
561 Type_Filter_Balance -> "FILTER_OF_BALANCE"
562 Type_Filter_General_Ledger -> "FILTER_OF_GENERAL_LEDGER"
563 Type_Filter_Posting -> "FILTER_OF_POSTING"
564 Type_Filter_Tag -> "FILTER_OF_TAG"
565 Type_Filter_Transaction -> "FILTER_OF_TRANSACTION"
566 Type_Option -> "OPTION"
567 translate FR t =
568 case t of
569 Type_Account -> "COMPTE"
570 Type_File -> "FICHIER"
571 Type_File_Journal -> "FICHIER_DE_JOURNAL"
572 Type_Filter_Balance -> "FILTRE_DE_BALANCE"
573 Type_Filter_General_Ledger -> "FILTRE_DE_GRAND_LIVRE"
574 Type_Filter_Posting -> "FILTRE_DE_MOUVEMENT"
575 Type_Filter_Tag -> "FILTRE_DE_TAG"
576 Type_Filter_Transaction -> "FILTRE_D’ÉCRITURE"
577 Type_Option -> "PARAMÈTRE"
578
579 -- * Type 'Write'
580 data Write
581 = Write_Debug
582 | Write_Error
583 instance Translate Write W.Doc where
584 translate EN t =
585 case t of
586 Write_Error -> "ERROR"
587 Write_Debug -> "DEBUG"
588 translate FR t =
589 case t of
590 Write_Error -> "ERREUR"
591 Write_Debug -> "DÉBUG"
592