]> Git — Sourcephile - comptalang.git/blob - lib/Hcompta/Filter/Read.hs
Ajout : Filter : Filter_Account : Order.
[comptalang.git] / lib / Hcompta / Filter / Read.hs
1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE NamedFieldPuns #-}
4 {-# LANGUAGE ScopedTypeVariables #-}
5 {-# LANGUAGE TypeFamilies #-}
6 module Hcompta.Filter.Read where
7
8 import Prelude hiding (filter)
9 -- import Control.Applicative ((<$>), (<*))
10 import Control.Exception (assert)
11 import Control.Monad (liftM, join, when)
12 -- import Control.Monad.Trans.Except (ExceptT(..), throwE)
13 import qualified Data.Char
14 import Data.Data
15 import qualified Data.Foldable
16 import Data.Functor.Identity (Identity)
17 import Data.Maybe (catMaybes)
18 import qualified Data.Time.Clock as Time
19 import qualified Text.Parsec.Expr as R
20 import qualified Text.Parsec as R hiding
21 ( char
22 , anyChar
23 , crlf
24 , newline
25 , noneOf
26 , oneOf
27 , satisfy
28 , space
29 , spaces
30 , string
31 )
32 -- import qualified Text.Parsec.Expr as R
33 import Text.Parsec (Stream, ParsecT, (<|>), (<?>))
34 import Data.String (fromString)
35 import qualified Data.Text as Text
36 import Data.Text (Text)
37 import Data.Typeable ()
38
39 import Hcompta.Lib.Interval (Interval)
40 import qualified Hcompta.Lib.Interval as Interval
41 import qualified Hcompta.Lib.Regex as Regex
42 -- import Hcompta.Lib.Regex (Regex)
43 import qualified Hcompta.Account as Account
44 import qualified Hcompta.Amount as Amount
45 import Hcompta.Amount (Amount)
46 import qualified Hcompta.Amount.Read as Amount.Read
47 import qualified Hcompta.Amount.Unit as Unit
48 import qualified Hcompta.Date as Date
49 import Hcompta.Date (Date)
50 import qualified Hcompta.Date.Read as Date.Read
51 import qualified Hcompta.Filter as Filter
52 import Hcompta.Filter hiding (Amount)
53 import qualified Hcompta.Lib.Parsec as R
54
55 -- * Parsers' types
56
57 -- ** Type 'Context'
58
59 data Context
60 = Context
61 { context_date :: Date
62 } deriving (Data, Eq, Show, Typeable)
63
64 context :: Context
65 context =
66 Context
67 { context_date = Date.nil
68 }
69
70 -- ** Type 'Error'
71
72 data Error
73 = Error_Unknown
74 | Error_Filter_Date Date.Read.Error
75 | Error_Filter_Date_Interval (Integer, Integer)
76 deriving (Show)
77
78 -- * Read
79
80 read ::
81 ( Stream s (R.Error_State Error Identity) Char
82 , Show t
83 )
84 => ParsecT s Context (R.Error_State Error Identity) (Filter_Bool t)
85 -> s -> IO (Either [R.Error Error] (Filter_Bool t))
86 read t s = do
87 context_date <- Time.getCurrentTime
88 return $
89 R.runParser_with_Error t context{context_date} "" s
90
91 -- ** Read 'Filter_Text'
92 filter_text
93 :: (Stream s m Char, Monad r)
94 => ParsecT s u m (String -> r Filter_Text)
95 filter_text =
96 R.choice_try
97 [ R.char '~' >> return (\s -> Regex.of_StringM s >>= (return . Filter_Text_Regex))
98 , R.char '=' >> return (\s -> return (Filter_Text_Exact $ Text.pack s))
99 , return (\s -> return (Filter_Text_Exact $ Text.pack s))
100 ]
101
102 filter_text_operator
103 :: Stream s m Char
104 => ParsecT s u m String
105 filter_text_operator =
106 R.choice_try
107 [ R.string "="
108 , R.string "~"
109 ]
110
111 -- ** Read 'Filter_Ord'
112 filter_ord
113 :: (Stream s m Char, Ord o)
114 => ParsecT s u m (o -> Filter_Ord o)
115 filter_ord =
116 R.choice_try
117 [ R.string "=" >> return (Filter_Ord Eq)
118 , R.string "<=" >> return (Filter_Ord Le) -- NOTE: before "<"
119 , R.string ">=" >> return (Filter_Ord Ge) -- NOTE: before ">"
120 , R.string "<" >> return (Filter_Ord Lt)
121 , R.string ">" >> return (Filter_Ord Gt)
122 ]
123
124 filter_ord_operator
125 :: Stream s m Char
126 => ParsecT s u m String
127 filter_ord_operator =
128 R.choice_try
129 [ R.string "="
130 , R.string "<="
131 , R.string ">="
132 , R.string "<"
133 , R.string ">"
134 ]
135
136 -- ** Read 'Filter_Num_Abs'
137 filter_num_abs
138 :: (Stream s m Char, Num n)
139 => ParsecT s u m (Filter_Ord n -> m (Either (Filter_Ord n) (Filter_Num_Abs n)))
140 filter_num_abs =
141 R.choice_try
142 [ R.char '+' >> return (return . Right . Filter_Num_Abs)
143 , return (return . Left)
144 ]
145
146 text :: Stream s m Char => String -> ParsecT s Context m Text
147 text none_of =
148 fromString <$>
149 R.choice_try
150 [ borders inside
151 , R.many $ R.noneOf ("() " ++ none_of)
152 ]
153 where
154 borders = R.between (R.char '(') (R.char ')')
155 inside = liftM concat $ R.many (R.choice_try [borders preserve_inside, R.many1 $ R.noneOf "()"])
156 preserve_inside = inside >>= (\x -> return $ '(':(x++')':[]))
157
158 -- ** Read 'Filter_Bool'
159
160 filter_bool
161 :: (Stream s m Char)
162 => [ParsecT s u m (ParsecT s u m t)]
163 -> ParsecT s u m (Filter_Bool t)
164 filter_bool terms =
165 R.buildExpressionParser
166 filter_bool_operators
167 (filter_bool_term terms)
168 <?> "filter_bool"
169
170 filter_bool_operators
171 :: Stream s m Char
172 => R.OperatorTable s u m (Filter.Filter_Bool t)
173 filter_bool_operators =
174 [ [ prefix "- " Filter.Not
175 ]
176 , [ binary " & " Filter.And R.AssocLeft
177 ]
178 , [ binary " + " Filter.Or R.AssocLeft
179 , binary " - " (\x -> Filter.And x . Filter.Not) R.AssocLeft
180 ]
181 ]
182 where
183 binary name fun assoc = R.Infix (filter_bool_operator name >> return fun) assoc
184 prefix name fun = R.Prefix (filter_bool_operator name >> return fun)
185 -- postfix name fun = Text.Parsec.Expr.Postfix (filter_bool_operator name >> return fun)
186
187 filter_bool_operator
188 :: Stream s m Char
189 => String -> ParsecT s u m ()
190 filter_bool_operator name =
191 R.try $
192 (R.string name
193 >> R.notFollowedBy filter_bool_operator_letter
194 -- <* R.spaces
195 <?> name)
196
197 filter_bool_operator_letter
198 :: Stream s m Char => ParsecT s u m Char
199 filter_bool_operator_letter =
200 R.oneOf ['-', '&', '+']
201
202 filter_bool_term
203 :: Stream s m Char
204 => [ParsecT s u m (ParsecT s u m t)]
205 -> ParsecT s u m (Filter_Bool t)
206 filter_bool_term terms = do
207 join (R.choice_try
208 ( (R.lookAhead (R.try (R.spaces >> R.char '('))
209 >> (return $ parens $
210 Data.Foldable.foldr Filter.And Filter.Any <$>
211 R.many (R.try (R.spaces >> expr)) ))
212 : map ((Filter.Bool <$>) <$>) terms
213 ) <* R.spaces <?> "boolean-expression")
214 where
215 expr =
216 R.lookAhead (R.try R.anyToken)
217 >> R.notFollowedBy (R.char ')')
218 >> filter_bool terms
219
220 parens
221 :: Stream s m Char
222 => ParsecT s u m a
223 -> ParsecT s u m a
224 parens =
225 R.between
226 (R.spaces >> R.char '(')
227 (R.spaces >> R.char ')')
228
229 bool :: Stream s m Char => ParsecT s u m Bool
230 bool = do
231 R.choice_try
232 [ R.choice_try
233 [ R.string "1"
234 , R.string "true"
235 , R.string "t"
236 ] >> return True
237 , R.choice_try
238 [ R.string "0"
239 , R.string "false"
240 , R.string "f"
241 ] >> return False
242 ]
243
244 jump :: Stream s m Char
245 => [String]
246 -> ParsecT s u m b
247 -> a
248 -> ParsecT s u m a
249 jump prefixes next r =
250 R.choice_try
251 (map (\s -> R.string s >> return r) prefixes)
252 <* R.lookAhead (R.try next)
253
254 -- ** Read Account.'Account.Name'
255 account_name :: Stream s m Char => ParsecT s u m Account.Name
256 account_name = do
257 fromString <$> do
258 R.many1 $ R.try account_name_char
259 where
260 account_name_char :: Stream s m Char => ParsecT s u m Char
261 account_name_char = do
262 c <- R.anyChar
263 case c of
264 -- _ | c == comment_begin -> R.parserZero
265 -- _ | c == account_section_sep -> R.parserZero
266 _ | R.is_space_horizontal c -> do
267 _ <- R.notFollowedBy $ R.space_horizontal
268 return c <* (R.lookAhead $ R.try $
269 ( R.try (R.char account_section_sep)
270 <|> account_name_char
271 ))
272 _ | not (Data.Char.isSpace c) -> return c
273 _ -> R.parserZero
274
275 -- ** Read 'Filter_Account_Section'
276 filter_account_section
277 :: (Stream s m Char)
278 => ParsecT s u m Filter_Account_Section
279 filter_account_section = do
280 R.choice_try
281 [ R.char '*'
282 <* R.lookAhead account_section_end
283 >> return Filter_Account_Section_Any
284 , R.char '~'
285 >> R.many1 (R.satisfy (\c -> c /= account_section_sep && not (Data.Char.isSpace c)))
286 >>= (liftM (Filter_Account_Section_Text . Filter_Text_Regex) . Regex.of_StringM)
287 , R.many1 (R.satisfy (\c -> c /= account_section_sep && not (Data.Char.isSpace c)))
288 >>= (liftM (Filter_Account_Section_Text . Filter_Text_Exact) . return . Text.pack)
289 , R.lookAhead account_section_end
290 >> R.many (R.try (R.char account_section_sep >> R.lookAhead (R.try account_section_end)))
291 >> return Filter_Account_Section_Many
292 ]
293 where
294 account_section_end =
295 R.choice_try
296 [ R.char account_section_sep >> return ()
297 , R.space_horizontal >> return ()
298 , R.eof
299 ]
300
301 -- ** Read 'Filter_Account'
302 account_section_sep :: Char
303 account_section_sep = ':'
304
305 filter_account
306 :: Stream s m Char
307 => ParsecT s u m Filter_Account
308 filter_account = do
309 R.notFollowedBy $ R.space_horizontal
310 Filter_Ord o () <-
311 R.option (Filter_Ord Eq ()) $ R.try $
312 (\f -> f ()) <$> filter_ord
313 fmap (Filter_Account o) $
314 R.many1_separated filter_account_section $
315 R.char account_section_sep
316
317 filter_account_operator
318 :: Stream s m Char
319 => ParsecT s u m String
320 filter_account_operator =
321 filter_text_operator
322
323 -- ** Read 'Filter_Amount'
324 filter_amount
325 :: Stream s m Char
326 => ParsecT s u m (Filter_Amount Amount)
327 filter_amount = do
328 R.notFollowedBy $ R.space_horizontal
329 R.choice_try
330 [ filter_ord
331 >>= \tst -> do
332 amt <- Amount.Read.amount
333 return $
334 (Filter_Amount_Section_Quantity (tst $ Amount.quantity amt))
335 : case Unit.text $ Amount.unit amt of
336 unit | Text.null unit -> []
337 unit -> [Filter_Amount_Section_Unit (Filter_Unit (Filter_Text_Exact unit))]
338 , filter_text
339 >>= \tst -> do
340 unit <- Amount.Read.unit >>= tst . Text.unpack . Unit.text
341 return $ [Filter_Amount_Section_Unit (Filter_Unit unit)]
342 ]
343
344 filter_amount_operator
345 :: Stream s m Char
346 => ParsecT s u m String
347 filter_amount_operator =
348 R.choice_try
349 [ filter_ord_operator
350 , filter_text_operator
351 ]
352
353 -- ** Read 'Filter_Date'
354 filter_date
355 :: (Stream s (R.Error_State Error m) Char, Monad m)
356 => ParsecT s Context (R.Error_State Error m) (Filter_Bool Filter_Date)
357 filter_date = do
358 join $ R.choice_try
359 [ R.char '=' >>
360 (return $ read_date_pattern)
361 , filter_ord >>= \tst ->
362 return $ do
363 ctx <- R.getState
364 let (year, _, _) = Date.gregorian $ context_date ctx
365 Date.Read.date Error_Filter_Date (Just year)
366 >>= return . Bool . Filter_Date_UTC . tst
367 ]
368 where
369 read_date_pattern
370 :: (Stream s (R.Error_State Error m) Char, Monad m)
371 => ParsecT s u (R.Error_State Error m) (Filter_Bool Filter_Date)
372 read_date_pattern = (do
373 let read2 = of_digits <$> (R.try (R.count 2 R.digit) <|> R.count 1 R.digit)
374 n0 <- read_interval Error_Filter_Date_Interval $ of_digits <$> R.many1 R.digit
375 n1 <- R.option Nothing $ R.try $ do
376 _ <- R.char '/'
377 Just <$> read_interval Error_Filter_Date_Interval read2
378 n2 <- R.option Nothing $ R.try $ do
379 _ <- R.char '/'
380 Just <$> read_interval Error_Filter_Date_Interval read2
381 let (year, month, dom) =
382 case (n1, n2) of
383 (Nothing, Nothing) ->
384 ( Interval.unlimited
385 , n0
386 , Interval.unlimited )
387 (Just d1, Nothing) ->
388 ( Interval.unlimited
389 , n0
390 , d1 )
391 (Nothing, Just _d2) -> assert False undefined
392 (Just d1, Just d2) ->
393 ( n0
394 , d1
395 , d2 )
396 (hour, minute, second) <-
397 R.option (Interval.unlimited, Interval.unlimited, Interval.unlimited) $ R.try $ do
398 R.skipMany1 $ R.space_horizontal
399 hour <- read_interval Error_Filter_Date_Interval read2
400 sep <- Date.Read.hour_separator
401 minute <- read_interval Error_Filter_Date_Interval read2
402 second <- R.option Interval.unlimited $ R.try $ do
403 _ <- R.char sep
404 read_interval Error_Filter_Date_Interval $ of_digits <$> R.many1 R.digit
405 -- tz <- R.option Time.utc $ R.try $ do
406 -- R.skipMany $ R.space_horizontal
407 -- Date.Read.time_zone
408 return
409 ( hour
410 , minute
411 , second
412 )
413 return $
414 foldr And Any $
415 catMaybes $
416 [ just_when_limited (Filter_Date_Year . Filter_Interval_In) year
417 , just_when_limited (Filter_Date_Month . Filter_Interval_In) (Interval.fmap_unsafe (fmap fromInteger) month)
418 , just_when_limited (Filter_Date_DoM . Filter_Interval_In) (Interval.fmap_unsafe (fmap fromInteger) dom)
419 , just_when_limited (Filter_Date_Hour . Filter_Interval_In) (Interval.fmap_unsafe (fmap fromInteger) hour)
420 , just_when_limited (Filter_Date_Minute . Filter_Interval_In) (Interval.fmap_unsafe (fmap fromInteger) minute)
421 , just_when_limited (Filter_Date_Second . Filter_Interval_In) (Interval.fmap_unsafe (fmap fromInteger) second)
422 ]
423 ) <?> "date-filter"
424 where
425 of_digits :: Num n => [Char] -> n
426 of_digits = fromInteger . R.integer_of_digits 10
427 just_when_limited f x =
428 if x == Interval.unlimited
429 then Nothing
430 else Just $ Bool $ f x
431
432 read_interval
433 :: (Stream s (R.Error_State e m) Char, Monad m, Ord x)
434 => ((x, x) -> e)
435 -> ParsecT s u (R.Error_State e m) x
436 -> ParsecT s u (R.Error_State e m) (Interval (Interval.Unlimitable x))
437 read_interval err read_digits = do
438 l <- R.choice_try
439 [ R.string ".." >> return Interval.Unlimited_low
440 , Interval.Limited <$> read_digits
441 ]
442 R.choice_try
443 [ when (l /= Interval.Unlimited_low)
444 (R.string ".." >> return ()) >> do
445 h <- R.choice_try
446 [ Interval.Limited <$> read_digits
447 , return Interval.Unlimited_high
448 ]
449 case (Interval.<=..<=) l h of
450 Nothing -> R.fail_with "interval" (err $ (Interval.limited l, Interval.limited h))
451 Just i -> return i
452 , return $
453 case l of
454 Interval.Limited _ -> Interval.point l
455 _ -> Interval.unlimited
456 ]
457
458 filter_date_operator
459 :: Stream s m Char
460 => ParsecT s u m String
461 filter_date_operator =
462 filter_ord_operator
463
464 -- ** Read 'Filter_Tag'
465 tag_name_sep :: Char
466 tag_name_sep = ':'
467
468 filter_tag_name
469 :: Stream s m Char
470 => ParsecT s u m Filter_Tag
471 filter_tag_name = do
472 make_filter_text <- filter_text
473 R.choice_try
474 [ R.char '*'
475 <* R.lookAhead filter_tag_name_end
476 >> return (Filter_Tag_Name Filter_Text_Any)
477 , R.many1 (R.notFollowedBy (R.try filter_tag_name_end) >> R.anyChar)
478 >>= (liftM Filter_Tag_Name . make_filter_text)
479 ]
480 where
481 filter_tag_name_end =
482 R.choice_try
483 [ filter_text_operator >> return ()
484 , R.space_horizontal >> return ()
485 , R.eof
486 ]
487 filter_tag_value
488 :: Stream s m Char
489 => ParsecT s u m Filter_Tag
490 filter_tag_value = do
491 make_filter_text <- filter_text
492 R.choice_try
493 [ R.char '*'
494 <* R.lookAhead filter_tag_value_end
495 >> return (Filter_Tag_Value Filter_Text_Any)
496 , R.many1 (R.notFollowedBy (R.try filter_tag_value_end) >> R.anyChar)
497 >>= (liftM Filter_Tag_Value . make_filter_text)
498 ]
499 where
500 filter_tag_value_end =
501 R.choice_try
502 [ R.space_horizontal >> return ()
503 , R.eof
504 ]
505
506 filter_tag
507 :: Stream s m Char
508 => ParsecT s u m (Filter_Bool Filter_Tag)
509 filter_tag = do
510 n <- filter_tag_name
511 R.choice_try
512 [ R.lookAhead (R.try $ filter_tag_operator)
513 >> And (Bool n) . Bool <$> filter_tag_value
514 , return $ Bool n
515 ]
516
517 filter_tag_operator
518 :: Stream s m Char
519 => ParsecT s u m String
520 filter_tag_operator =
521 filter_text_operator
522
523 -- ** Read 'Filter_Posting'
524 filter_posting
525 :: (Stream s m Char, Filter.Posting t)
526 => ParsecT s Context m (Filter_Bool (Filter_Posting t))
527 filter_posting =
528 Data.Foldable.foldr Filter.And Filter.Any <$>
529 do R.many $
530 R.spaces
531 >> R.lookAhead R.anyToken
532 >> filter_bool filter_posting_terms
533
534 filter_posting_terms
535 :: (Stream s m Char, Filter.Posting t)
536 => [ParsecT s Context m (ParsecT s Context m (Filter_Posting t))]
537 filter_posting_terms =
538 [ return
539 ( Filter.Filter_Posting_Account
540 <$> filter_account )
541 ]
542
543 -- ** Read 'Filter_Transaction'
544 filter_transaction
545 :: (Stream s (R.Error_State Error m) Char, Monad m, Filter.Transaction t
546 , Posting_Amount (Transaction_Posting t) ~ Amount)
547 => ParsecT s Context (R.Error_State Error m) (Filter_Bool (Filter_Transaction t))
548 filter_transaction =
549 Data.Foldable.foldr Filter.And Filter.Any <$>
550 do R.many $
551 R.spaces
552 >> R.lookAhead R.anyToken
553 >> filter_bool filter_transaction_terms
554
555 filter_transaction_terms
556 :: (Stream s (R.Error_State Error m) Char, Filter.Transaction t, Monad m
557 , Posting_Amount (Transaction_Posting t) ~ Amount)
558 => [ParsecT s Context (R.Error_State Error m)
559 (ParsecT s Context (R.Error_State Error m) (Filter_Transaction t))]
560 filter_transaction_terms =
561 -- , jump [ "atag" ] comp_text parseFilterATag
562 -- , jump [ "code" ] comp_text parseFilterCode
563 [ jump [ "date" ] filter_date_operator
564 (Filter.Filter_Transaction_Date <$> filter_date)
565 , jump [ "tag" ] filter_tag_operator
566 (Filter.Filter_Transaction_Tag <$> filter_tag)
567 , jump [ "amount" ] filter_amount_operator
568 (( Filter.Filter_Transaction_Posting
569 . Filter.Filter_Posting_Amount
570 ) <$> filter_amount)
571 -- , jump [ "date2", "edate" ] (R.char '=') parseFilterDate2
572 -- , jump [ "description","descr","desc" ] comp_text parseFilterDesc
573 -- , jump [ "real" ] (R.char '=') parseFilterReal
574 -- , jump [ "status" ] (R.char '=') parseFilterStatus
575 -- , jump [ "sym" ] comp_text parseFilterSym
576 -- , R.lookAhead comp_num >> return parseFilterAmount
577 , return
578 ( Filter.Filter_Transaction_Posting
579 . Filter.Filter_Posting_Account
580 <$> filter_account )
581 ]
582
583 -- ** Read 'Filter_Balance'
584 filter_balance
585 :: (Stream s m Char, Filter.Balance t, Balance_Amount t ~ Amount)
586 => ParsecT s Context m (Filter_Bool (Filter_Balance t))
587 filter_balance =
588 Data.Foldable.foldr Filter.And Filter.Any <$>
589 do R.many $
590 R.spaces
591 >> R.lookAhead R.anyToken
592 >> filter_bool filter_balance_terms
593
594 filter_balance_terms
595 :: (Stream s m Char, Filter.Balance t, Balance_Amount t ~ Amount)
596 => [ParsecT s Context m (ParsecT s Context m (Filter_Balance t))]
597 filter_balance_terms =
598 [ jump [ "D" ] filter_amount_operator
599 ( Filter.Filter_Balance_Positive
600 <$> filter_amount )
601 , jump [ "C" ] filter_amount_operator
602 ( Filter.Filter_Balance_Negative
603 <$> filter_amount )
604 , jump [ "B" ] filter_amount_operator
605 ( Filter.Filter_Balance_Amount
606 <$> filter_amount )
607 , return
608 ( Filter.Filter_Balance_Account
609 <$> filter_account )
610 ]
611
612 -- ** Read 'Filter_GL'
613 filter_gl
614 :: (Stream s m Char, Filter.GL t, GL_Amount t ~ Amount)
615 => ParsecT s Context m (Filter_Bool (Filter_GL t))
616 filter_gl =
617 Data.Foldable.foldr Filter.And Filter.Any <$>
618 do R.many $
619 R.spaces
620 >> R.lookAhead R.anyToken
621 >> filter_bool filter_gl_terms
622
623 filter_gl_terms
624 :: (Stream s m Char, Filter.GL t, GL_Amount t ~ Amount)
625 => [ParsecT s Context m (ParsecT s Context m (Filter_GL t))]
626 filter_gl_terms =
627 [ jump [ "D" ] filter_amount_operator
628 ( Filter.Filter_GL_Amount_Positive
629 <$> filter_amount )
630 , jump [ "C" ] filter_amount_operator
631 ( Filter.Filter_GL_Amount_Negative
632 <$> filter_amount )
633 , jump [ "B" ] filter_amount_operator
634 ( Filter.Filter_GL_Amount_Balance
635 <$> filter_amount )
636 , jump [ "RD" ] filter_amount_operator
637 ( Filter.Filter_GL_Sum_Positive
638 <$> filter_amount )
639 , jump [ "RC" ] filter_amount_operator
640 ( Filter.Filter_GL_Sum_Negative
641 <$> filter_amount )
642 , jump [ "RB" ] filter_amount_operator
643 ( Filter.Filter_GL_Sum_Balance
644 <$> filter_amount )
645 , return
646 ( Filter.Filter_GL_Account
647 <$> filter_account )
648 ]