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