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