lib: refactor sign parser
- Extracts the handling of signs out of `fromRawNumber` and into `signp` itself - Rationale: The sign can be applied independently from the logic in `fromRawNumber`
This commit is contained in:
		
							parent
							
								
									d28862d10d
								
							
						
					
					
						commit
						cf9b2001e7
					
				| @ -101,7 +101,7 @@ import Control.Monad.State.Strict | |||||||
| import Data.Bifunctor | import Data.Bifunctor | ||||||
| import Data.Char | import Data.Char | ||||||
| import Data.Data | import Data.Data | ||||||
| import Data.Decimal (DecimalRaw (Decimal), Decimal) | import Data.Decimal (DecimalRaw (Decimal)) | ||||||
| import Data.Default | import Data.Default | ||||||
| import Data.Functor.Identity | import Data.Functor.Identity | ||||||
| import Data.List.Compat | import Data.List.Compat | ||||||
| @ -534,11 +534,8 @@ amountp' s = | |||||||
| mamountp' :: String -> MixedAmount | mamountp' :: String -> MixedAmount | ||||||
| mamountp' = Mixed . (:[]) . amountp' | mamountp' = Mixed . (:[]) . amountp' | ||||||
| 
 | 
 | ||||||
| signp :: TextParser m String | signp :: Num a => TextParser m (a -> a) | ||||||
| signp = do | signp = char '-' *> pure negate <|> char '+' *> pure id <|> pure id | ||||||
|   sign <- optional $ oneOf ("+-" :: [Char]) |  | ||||||
|   return $ case sign of Just '-' -> "-" |  | ||||||
|                         _        -> "" |  | ||||||
| 
 | 
 | ||||||
| multiplierp :: TextParser m Bool | multiplierp :: TextParser m Bool | ||||||
| multiplierp = option False $ char '*' *> pure True | multiplierp = option False $ char '*' *> pure True | ||||||
| @ -565,8 +562,7 @@ leftsymbolamountp = do | |||||||
|   (q,prec,mdec,mgrps) <- lift $ numberp suggestedStyle |   (q,prec,mdec,mgrps) <- lift $ numberp suggestedStyle | ||||||
|   let s = amountstyle{ascommodityside=L, ascommodityspaced=commodityspaced, asprecision=prec, asdecimalpoint=mdec, asdigitgroups=mgrps} |   let s = amountstyle{ascommodityside=L, ascommodityspaced=commodityspaced, asprecision=prec, asdecimalpoint=mdec, asdigitgroups=mgrps} | ||||||
|   p <- priceamountp |   p <- priceamountp | ||||||
|   let applysign = if sign=="-" then negate else id |   return $ Amount c (sign q) p s m | ||||||
|   return $ applysign $ Amount c q p s m |  | ||||||
|   <?> "left-symbol amount" |   <?> "left-symbol amount" | ||||||
| 
 | 
 | ||||||
| rightsymbolamountp :: Monad m => JournalParser m Amount | rightsymbolamountp :: Monad m => JournalParser m Amount | ||||||
| @ -578,8 +574,8 @@ rightsymbolamountp = do | |||||||
|   commodityspaced <- lift $ skipMany' spacenonewline |   commodityspaced <- lift $ skipMany' spacenonewline | ||||||
|   c <- lift commoditysymbolp |   c <- lift commoditysymbolp | ||||||
|   suggestedStyle <- getAmountStyle c |   suggestedStyle <- getAmountStyle c | ||||||
|   let (q0,prec0,mdec,mgrps) = fromRawNumber suggestedStyle (sign == "-") rawnum |   let (q0,prec0,mdec,mgrps) = fromRawNumber suggestedStyle rawnum | ||||||
|       (q, prec) = expMod (q0, prec0) |       (q, prec) = expMod (sign q0, prec0) | ||||||
|   p <- priceamountp |   p <- priceamountp | ||||||
|   let s = amountstyle{ascommodityside=R, ascommodityspaced=commodityspaced, asprecision=prec, asdecimalpoint=mdec, asdigitgroups=mgrps} |   let s = amountstyle{ascommodityside=R, ascommodityspaced=commodityspaced, asprecision=prec, asdecimalpoint=mdec, asdigitgroups=mgrps} | ||||||
|   return $ Amount c q p s m |   return $ Amount c q p s m | ||||||
| @ -677,17 +673,22 @@ numberp suggestedStyle = do | |||||||
|     sign <- signp |     sign <- signp | ||||||
|     raw <- rawnumberp |     raw <- rawnumberp | ||||||
|     dbg8 "numberp suggestedStyle" suggestedStyle `seq` return () |     dbg8 "numberp suggestedStyle" suggestedStyle `seq` return () | ||||||
|     let num@(q, prec, decSep, groups) = dbg8 "numberp quantity,precision,mdecimalpoint,mgrps" (fromRawNumber suggestedStyle (sign == "-") raw) |     let (q, prec, decSep, groups) = | ||||||
|     option num . try $ do |           dbg8 "numberp quantity,precision,mdecimalpoint,mgrps" | ||||||
|         when (isJust groups) $ fail "groups and exponent are not mixable" |             $ fromRawNumber suggestedStyle raw | ||||||
|         (q', prec') <- exponentp <*> pure (q, prec) |     mExp <- optional $ try $ exponentp | ||||||
|         return (q', prec', decSep, groups) |     case mExp of | ||||||
|  |       Just expFunc | ||||||
|  |         | isJust groups -> fail "groups and exponent are not mixable" | ||||||
|  |         | otherwise -> let (q', prec') = expFunc (q, prec) | ||||||
|  |                        in  pure (sign q', prec', decSep, groups) | ||||||
|  |       Nothing -> pure (sign q, prec, decSep, groups) | ||||||
|     <?> "numberp" |     <?> "numberp" | ||||||
| 
 | 
 | ||||||
| exponentp :: TextParser m ((Quantity, Int) -> (Quantity, Int)) | exponentp :: TextParser m ((Quantity, Int) -> (Quantity, Int)) | ||||||
| exponentp = do | exponentp = do | ||||||
|     char' 'e' |     char' 'e' | ||||||
|     exp <- liftM read $ (++) <$> signp <*> some digitChar |     exp <- ($) <$> signp <*> (read <$> some digitChar) | ||||||
|     return $ bimap (* 10^^exp) (max 0 . subtract exp) |     return $ bimap (* 10^^exp) (max 0 . subtract exp) | ||||||
|     <?> "exponentp" |     <?> "exponentp" | ||||||
| 
 | 
 | ||||||
| @ -704,25 +705,24 @@ exponentp = do | |||||||
| -- - the digit group style, if any (digit group character and sizes of digit groups) | -- - the digit group style, if any (digit group character and sizes of digit groups) | ||||||
| fromRawNumber | fromRawNumber | ||||||
|   :: Maybe AmountStyle |   :: Maybe AmountStyle | ||||||
|   -> Bool |  | ||||||
|   -> RawNumber |   -> RawNumber | ||||||
|   -> (Quantity, Int, Maybe Char, Maybe DigitGroupStyle) |   -> (Quantity, Int, Maybe Char, Maybe DigitGroupStyle) | ||||||
| fromRawNumber suggestedStyle negated raw = case raw of | fromRawNumber suggestedStyle raw = case raw of | ||||||
| 
 | 
 | ||||||
|   LeadingDecimalPt decPt digitGrp -> |   LeadingDecimalPt decPt digitGrp -> | ||||||
|     let quantity = sign $ |     let quantity = | ||||||
|           Decimal (fromIntegral precision) (digitGroupNumber digitGrp) |           Decimal (fromIntegral precision) (digitGroupNumber digitGrp) | ||||||
|         precision = digitGroupLength digitGrp |         precision = digitGroupLength digitGrp | ||||||
|     in  (quantity, precision, Just decPt, Nothing) |     in  (quantity, precision, Just decPt, Nothing) | ||||||
| 
 | 
 | ||||||
|   TrailingDecimalPt digitGrp decPt -> |   TrailingDecimalPt digitGrp decPt -> | ||||||
|     let quantity = sign $ |     let quantity = | ||||||
|           Decimal (fromIntegral precision) (digitGroupNumber digitGrp) |           Decimal (fromIntegral precision) (digitGroupNumber digitGrp) | ||||||
|         precision = 0 |         precision = 0 | ||||||
|     in  (quantity, precision, Just decPt, Nothing) |     in  (quantity, precision, Just decPt, Nothing) | ||||||
| 
 | 
 | ||||||
|   NoSeparators digitGrp -> |   NoSeparators digitGrp -> | ||||||
|     let quantity = sign $ |     let quantity = | ||||||
|           Decimal (fromIntegral precision) (digitGroupNumber digitGrp) |           Decimal (fromIntegral precision) (digitGroupNumber digitGrp) | ||||||
|         precision = 0 |         precision = 0 | ||||||
|     in  (quantity, precision, Nothing, Nothing) |     in  (quantity, precision, Nothing, Nothing) | ||||||
| @ -734,7 +734,7 @@ fromRawNumber suggestedStyle negated raw = case raw of | |||||||
|       && maybe True (sep `isValidDecimalBy`) suggestedStyle -> |       && maybe True (sep `isValidDecimalBy`) suggestedStyle -> | ||||||
| 
 | 
 | ||||||
|       -- Assuming that the separator is a decimal point |       -- Assuming that the separator is a decimal point | ||||||
|       let quantity = sign $ |       let quantity = | ||||||
|             Decimal (fromIntegral precision) |             Decimal (fromIntegral precision) | ||||||
|                     (digitGroupNumber $ digitGrp1 <> digitGrp2) |                     (digitGroupNumber $ digitGrp1 <> digitGrp2) | ||||||
|           precision = digitGroupLength digitGrp2 |           precision = digitGroupLength digitGrp2 | ||||||
| @ -742,7 +742,7 @@ fromRawNumber suggestedStyle negated raw = case raw of | |||||||
| 
 | 
 | ||||||
|     | otherwise -> |     | otherwise -> | ||||||
|       -- Assuming that the separator is digit separator |       -- Assuming that the separator is digit separator | ||||||
|       let quantity = sign $ |       let quantity = | ||||||
|             Decimal (fromIntegral precision) |             Decimal (fromIntegral precision) | ||||||
|                     (digitGroupNumber $ digitGrp1 <> digitGrp2) |                     (digitGroupNumber $ digitGrp1 <> digitGrp2) | ||||||
|           precision = 0 |           precision = 0 | ||||||
| @ -751,7 +751,7 @@ fromRawNumber suggestedStyle negated raw = case raw of | |||||||
|       in  (quantity, precision, Nothing, digitGroupStyle) |       in  (quantity, precision, Nothing, digitGroupStyle) | ||||||
| 
 | 
 | ||||||
|   DigitSeparators digitSep digitGrps -> |   DigitSeparators digitSep digitGrps -> | ||||||
|     let quantity = sign $ |     let quantity = | ||||||
|           Decimal (fromIntegral precision) |           Decimal (fromIntegral precision) | ||||||
|                   (digitGroupNumber $ mconcat digitGrps) |                   (digitGroupNumber $ mconcat digitGrps) | ||||||
|         precision = 0 |         precision = 0 | ||||||
| @ -759,7 +759,7 @@ fromRawNumber suggestedStyle negated raw = case raw of | |||||||
|     in  (quantity, precision, Nothing, digitGroupStyle) |     in  (quantity, precision, Nothing, digitGroupStyle) | ||||||
| 
 | 
 | ||||||
|   BothSeparators digitSep digitGrps decPt decimalGrp -> |   BothSeparators digitSep digitGrps decPt decimalGrp -> | ||||||
|     let quantity = sign $ |     let quantity = | ||||||
|           Decimal (fromIntegral precision) |           Decimal (fromIntegral precision) | ||||||
|                   (digitGroupNumber $ mconcat digitGrps <> decimalGrp) |                   (digitGroupNumber $ mconcat digitGrps <> decimalGrp) | ||||||
|         precision = digitGroupLength decimalGrp |         precision = digitGroupLength decimalGrp | ||||||
| @ -767,10 +767,6 @@ fromRawNumber suggestedStyle negated raw = case raw of | |||||||
|     in  (quantity, precision, Just decPt, digitGroupStyle) |     in  (quantity, precision, Just decPt, digitGroupStyle) | ||||||
| 
 | 
 | ||||||
|   where |   where | ||||||
| 
 |  | ||||||
|     sign :: Decimal -> Decimal |  | ||||||
|     sign = if negated then negate else id |  | ||||||
| 
 |  | ||||||
|     -- Outputs digit group sizes from least significant to most significant |     -- Outputs digit group sizes from least significant to most significant | ||||||
|     groupSizes :: [DigitGrp] -> [Int] |     groupSizes :: [DigitGrp] -> [Int] | ||||||
|     groupSizes digitGrps = reverse $ case map digitGroupLength digitGrps of |     groupSizes digitGrps = reverse $ case map digitGroupLength digitGrps of | ||||||
|  | |||||||
		Loading…
	
		Reference in New Issue
	
	Block a user