Skip to content

Commit

Permalink
add support for YAML and obfuscated output
Browse files Browse the repository at this point in the history
    20190511-21:01:46 mengwong@venice4:~/src/l/openfisca-aotearoa/l4% stack exec aotearoa-exe -- additional_per_dependant=500 initial_contribution=160 maximum_allowable=620 income_threshold=24790 period=2018 combined_income=20000 rates_total=1000,2000 dependants=0,1 --goal=rr-br3nda-clip --nlgstyle=yaml
    - name: Someone with 0 dependants earning $20000 who paid $1000 in rates
      period: 2018
      absolute_error_margin: 1
      input:
        rates_rebates__combined_income: 20000
        rates_rebates__dependants: 0
        rates_rebates__rates_total: 1000
      output:
        rates_rebates__rebate: 560
    - name: Someone with 1 dependants earning $20000 who paid $1000 in rates
      period: 2018
      absolute_error_margin: 1
      input:
        rates_rebates__combined_income: 20000
        rates_rebates__dependants: 1
        rates_rebates__rates_total: 1000
      output:
        rates_rebates__rebate: 560
    - name: Someone with 0 dependants earning $20000 who paid $2000 in rates
      period: 2018
      absolute_error_margin: 1
      input:
        rates_rebates__combined_income: 20000
        rates_rebates__dependants: 0
        rates_rebates__rates_total: 2000
      output:
        rates_rebates__rebate: 620
    - name: Someone with 1 dependants earning $20000 who paid $2000 in rates
      period: 2018
      absolute_error_margin: 1
      input:
        rates_rebates__combined_income: 20000
        rates_rebates__dependants: 1
        rates_rebates__rates_total: 2000
      output:
        rates_rebates__rebate: 620

    20190511-21:01:46 mengwong@venice4:~/src/l/openfisca-aotearoa/l4% stack exec aotearoa-exe -- additional_per_dependant=500 initial_contribution=160 maximum_allowable=620 income_threshold=24790 period=2018 combined_income=20000 rates_total=1000,2000 dependants=0,1 --goal=rr-br3nda-clip
    +-------------+
    |   1000 2000 |
    | 0  560  620 |
    | 1  560  620 |
    +-------------+
    20190511-21:01:54 mengwong@venice4:~/src/l/openfisca-aotearoa/l4% stack exec aotearoa-exe -- additional_per_dependant=500 initial_contribution=160 maximum_allowable=620 income_threshold=24790 period=2018 combined_income=20000 rates_total=1000 dependants=0 --goal=rr-br3nda-clip --nlgstyle=obfuscated
    the goal, believe it or not, is
          so much of
          the rates payable for that rating year in respect of the property
        as represents
                  two-thirds of
              the amount by which
                the rates payable for that rating year in respect of the property
              exceeds
                160.00
          reduced by
            $1 for each $8
              by which
                the ratepayer's income for the preceding tax year
              exceeded
                  24790.00
                , that last-mentioned amount being increased by
                    500.00
                  in respect of each
                    person who was a dependant of the ratepayer at the commencement of the rating year in respect of which the application is made
      ; or
        620.00
    , whichever is lesser

    20190511-21:02:22 mengwong@venice4:~/src/l/openfisca-aotearoa/l4% stack exec aotearoa-exe -- additional_per_dependant=500 initial_contribution=160 maximum_allowable=620 income_threshold=24790 period=2018 combined_income=20000 rates_total=1000 dependants=0 --goal=rr-br3nda-clip --nlgstyle=abstract
    the goal is defined as
      the lesser of
        the lesser of
          the rates payable for that rating year in respect of the property
        and
          the greater of
          simply 0.00
          and
            the difference between
              two-thirds of
                the amount by which
                  the rates payable for that rating year in respect of the property
                exceeds
                  160.00
            and
              $1 for each $8 in
                the amount by which
                  the ratepayer's income for the preceding tax year
                exceeds
                  the sum of
                    24790.00
                  with
                    the product of
                      500.00
                    multiplied by
                      person who was a dependant of the ratepayer at the commencement of the rating year in respect of which the application is made
      and
        620.00
    20190511-21:02:26 mengwong@venice4:~/src/l/openfisca-aotearoa/l4% stack exec aotearoa-exe -- additional_per_dependant=500 initial_contribution=160 maximum_allowable=620 income_threshold=24790 period=2018 combined_income=20000 rates_total=1000 dependants=0 --goal=rr-br3nda-clip --nlgstyle=neutral
    the goal you're looking for is
      the lesser of
        the lesser of
          the rates payable for that rating year in respect of the property
        and
          the greater of
          simply 0.00
          and
            the difference between
              two-thirds of
                the amount by which
                  the rates payable for that rating year in respect of the property
                exceeds
                  the initial contribution by ratepayer, which is 160.00
            and
              $1 for each $8 in
                the amount by which
                  the ratepayer's income for the preceding tax year
                exceeds
                  the sum of
                    the income threshold, which is 24790.00
                  with
                    the product of
                      the additional allowable income per dependant, which is 500.00
                    multiplied by
                      person who was a dependant of the ratepayer at the commencement of the rating year in respect of which the application is made
      and
        the maximum rebate allowed, which is 620.00
    20190511-21:02:29 mengwong@venice4:~/src/l/openfisca-aotearoa/l4% stack exec aotearoa-exe -- additional_per_dependant=500 initial_contribution=160 maximum_allowable=620 income_threshold=24790 period=2018 combined_income=20000 rates_total=1000 dependants=0 --goal=rr-br3nda-clip --nlgstyle=concrete
    showing how we obtain the answer
    560.00 -- which is
      the lesser of
      560.00 -- which is
        the lesser of
        1000.00 -- which is
          rates_total, the rates payable for that rating year in respect of the property
        and
        560.00 -- which is
          the greater of
          simply 0.00
          and
          560.00 -- which is
            the difference between
            560.00 -- which is
              two-thirds of
              840.00 -- which is
                the amount by which
                1000.00 -- which is
                  rates_total, the rates payable for that rating year in respect of the property
                exceeds
                160.00 -- which is
                  initial_contribution, the initial contribution by ratepayer
            and
            0.00 -- which is
              $1 for each $8 in
              0.00 -- which is
                the amount by which
                20000.00 -- which is
                  combined_income, the ratepayer's income for the preceding tax year
                exceeds
                24790.00 -- which is
                  the sum of
                  24790.00 -- which is
                    income_threshold, the income threshold
                  with
                  0.00 -- which is
                    the product of
                    500.00 -- which is
                      additional_per_dependant, the additional allowable income per dependant
                    multiplied by
                    0.00 -- which is
                      dependants, person who was a dependant of the ratepayer at the commencement of the rating year in respect of which the application is made
      and
      620.00 -- which is
        maximum_allowable, the maximum rebate allowed
  • Loading branch information
mengwong committed May 11, 2019
1 parent a9eb65c commit 1d346f1
Show file tree
Hide file tree
Showing 4 changed files with 472 additions and 173 deletions.
18 changes: 16 additions & 2 deletions l4/README.md
Original file line number Diff line number Diff line change
Expand Up @@ -86,7 +86,15 @@ Run the executable:

## NLG Styles

Try other --nlgstyle values "abstract", "neutral", "concrete", and "algebra".
Try other --nlgstyle values:
- algebra
- concrete
- neutral
- abstract
- obfuscated
- yaml

Obfuscated may get you text which is eerily similar to actual legislation!

Concrete shows all numerical values used to arrive at the answer.

Expand Down Expand Up @@ -130,6 +138,8 @@ Abstract has the fewest numerical values.

Neutral is kind of a mix between the two.

Yaml produces test cases suitable for openfisca test.

## Ranges

You can also view tabular output by giving input ranges, using Haskell syntax:
Expand Down Expand Up @@ -222,7 +232,7 @@ The language available here is a fragment of L4 specialized for mathematical exp

Future releases of this software may integrate other L4 modules to:

- parse YAML, so it can run tests
- parse YAML, so it can import tests

- parse Python, (or at least OpenFisca's subset of Python), so it can read existing code

Expand All @@ -238,5 +248,9 @@ Future releases of this software may integrate other L4 modules to:

- output to other natural languages like Québécois

- output to LegalRuleML

- output to other languages like XAlgorithms and Accord Project's Ergo

- output to Excel format with formulas built in

200 changes: 165 additions & 35 deletions l4/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,14 +6,72 @@ module Main where
-- usage:
-- :main -v combined_income=32103 dependants=0 rates_total=2000 additional_per_dependant=500 initial_contribution=160 maximum_allowable=620 income_threshold=24790 --goal=rr-br3nda

-- :main -v additional_per_dependant=500 initial_contribution=160 maximum_allowable=620 income_threshold=24790 --goal=rr-br3nda --nlgstyle=algebra week_numDays=7
-- min((((2.00/3.00)*(rates_total-(initial_contribution=160.00)))-((combined_income-((income_threshold=24790.00)+((additional_per_dependant=500.00)*dependants)))/8.00)), (maximum_allowable=620.00))
-- :main -v additional_per_dependant=500 initial_contribution=160 maximum_allowable=620 income_threshold=24790 rates_total=400 combined_income=24000 dependants=2 --goal=rr-br3nda-noclip --nlgstyle=neutral
-- the goal you're looking for is
-- | the lesser of
-- | | the greater of
-- | | simply 0.00
-- | | and
-- | | | the difference between
-- | | | | the excess rates amount, which is
-- | | | | two-thirds
-- | | | | | the difference between
-- | | | | | | the total rates for the property
-- | | | | | and
-- | | | | | | the initial contribution by ratepayer, which is 160.00
-- | | | and
-- | | | | the income taper amount, which is
-- | | | | the quotient given by
-- | | | | | the income component adjusted for dependants, which is
-- | | | | | the difference between
-- | | | | | | the ratepayer's income for the preceding tax year
-- | | | | | and
-- | | | | | | the income taper trigger, which is
-- | | | | | | the sum of
-- | | | | | | | the income threshold, which is 24790.00
-- | | | | | | with
-- | | | | | | | the product of
-- | | | | | | | | the additional allowable income per dependant, which is 500.00
-- | | | | | | | multiplied by
-- | | | | | | | | the number of Persons classified as dependant for the purposes of Rates Rebates
-- | | | | divided by
-- | | | | simply 8.00
-- | and
-- | | the maximum rebate allowed, which is 620.00
--
-- :main -v additional_per_dependant=500 initial_contribution=160 maximum_allowable=620 income_threshold=24790 rates_total=100,200..2000 combined_income=12000,13000..30000 dependants=2 --goal=rr-br3nda-clip
-- +--------------------------------------------------------------------------------------------------+
-- | 100 200 300 400 500 600 700 800 900 1000 1100 1200 1300 1400 1500 1600 1700 1800 1900 2000 |
-- | 12000 0 27 93 160 227 293 360 427 493 560 620 620 620 620 620 620 620 620 620 620 |
-- | 13000 0 27 93 160 227 293 360 427 493 560 620 620 620 620 620 620 620 620 620 620 |
-- | 14000 0 27 93 160 227 293 360 427 493 560 620 620 620 620 620 620 620 620 620 620 |
-- | 15000 0 27 93 160 227 293 360 427 493 560 620 620 620 620 620 620 620 620 620 620 |
-- | 16000 0 27 93 160 227 293 360 427 493 560 620 620 620 620 620 620 620 620 620 620 |
-- | 17000 0 27 93 160 227 293 360 427 493 560 620 620 620 620 620 620 620 620 620 620 |
-- | 18000 0 27 93 160 227 293 360 427 493 560 620 620 620 620 620 620 620 620 620 620 |
-- | 19000 0 27 93 160 227 293 360 427 493 560 620 620 620 620 620 620 620 620 620 620 |
-- | 20000 0 27 93 160 227 293 360 427 493 560 620 620 620 620 620 620 620 620 620 620 |
-- | 21000 0 27 93 160 227 293 360 427 493 560 620 620 620 620 620 620 620 620 620 620 |
-- | 22000 0 27 93 160 227 293 360 427 493 560 620 620 620 620 620 620 620 620 620 620 |
-- | 23000 0 27 93 160 227 293 360 427 493 560 620 620 620 620 620 620 620 620 620 620 |
-- | 24000 0 27 93 160 227 293 360 427 493 560 620 620 620 620 620 620 620 620 620 620 |
-- | 25000 0 27 93 160 227 293 360 427 493 560 620 620 620 620 620 620 620 620 620 620 |
-- | 26000 0 0 67 134 200 267 334 400 467 534 600 620 620 620 620 620 620 620 620 620 |
-- | 27000 0 0 0 9 75 142 209 275 342 409 475 542 609 620 620 620 620 620 620 620 |
-- | 28000 0 0 0 0 0 17 84 150 217 284 350 417 484 550 617 620 620 620 620 620 |
-- | 29000 0 0 0 0 0 0 0 25 92 159 225 292 359 425 492 559 620 620 620 620 |
-- | 30000 0 0 0 0 0 0 0 0 0 34 100 167 234 300 367 434 500 567 620 620 |
-- +--------------------------------------------------------------------------------------------------+
-- ## 380 answers across 20 variations of rates_total * 19 variations of combined_income


import Lib
import Debug.Trace
import Data.Char
import Data.Matrix
import Data.List
import qualified Data.Text as Text
import Text.Read
import Data.List.Split
import qualified Data.Map as Map
import Data.Maybe
Expand Down Expand Up @@ -63,6 +121,8 @@ parseargs argv = case getOpt Permute flags argv of
splitOn = splitRegex . mkRegex
splitEq f = f <$> (Main.splitOn "=")

mkFSFD x y = (FS (Text.pack x), FD y)

splitToFSFD = splitEq (\a -> mkFSFD (a !! 0) (read (a !! 1) :: Double))

main :: IO ()
Expand All @@ -71,14 +131,14 @@ main = do
-- putStrLn $ "Flags: " ++ show flagargs
-- putStrLn $ "Dataargs: " ++ show dataargs
let goal = Data.List.find wantgoal flagargs
goalname = (Data.Maybe.fromMaybe
goalexpr = (Data.Maybe.fromMaybe
(error $ "goal not found; choose one of " ++ show (Map.keys goals))
(Map.lookup (getgoal goal) goals))
style = Data.List.find (\arg -> case arg of (NLGStyle _) -> True; _ -> False) flagargs
styleval = do
(NLGStyle x) <- style
y <- x
(Map.lookup y nlgstyles)
(Map.lookup (Text.pack y) nlgstyles)

-- if any input variables in the scenario have a range operator ".." in their value, then
-- respect [x,y..z] syntax from Haskell.
Expand All @@ -93,7 +153,13 @@ main = do
-- show single scenario
when (rangeArgs == []) $ do
let scenario = Map.fromList $ (\(a,b) -> mkFSFD a ((read b) :: Double)) <$> plainArgs
putStrLn $ runScenario (Env styleval scenario variables_dict) goalname
obfusgoal = case styleval of
-- Just VObfuscated -> obfuscate goalexpr
Just VObfuscated -> goalexpr
_ -> deobfuscate goalexpr
answer = runScenario (Env styleval scenario variables_dict) obfusgoal
when (styleval /= Just VYAML) $ putStrLn $ Text.unpack $ answer
when (styleval == Just VYAML) $ putStrLn $ dumpYAML scenario answer

when (rangeArgs /= []) $ do
-- putStrLn $ "## input contains range! the range args are " ++ show rangeArgs
Expand All @@ -103,12 +169,14 @@ main = do
rangearg <- rangeScenarios
let rangekey = fst rangearg
rangeval = snd rangearg
myrange = case length $ parseRange rangeval of
1 -> pure ((read rangeval) :: Int)
2 -> [(parseRange rangeval !! 0) .. (parseRange rangeval !! 1)]
3 -> [(parseRange rangeval !! 0) , (parseRange rangeval !! 1) .. (parseRange rangeval !! 2)]
myrange = case parseRange rangeval of
Just [(Just x)] -> [x]
Just [(Just x),(Just y),Nothing] -> [x,y]
Just [(Just x),Nothing,(Just y)] -> [x..y]
Just [(Just x),(Just y),(Just z)] -> [x,y..z]
_ -> error $ "can't parse range out of " ++ rangeval
return $ (rangekey, myrange)
let output = do
let answers = do
let rangekeys = fst <$> ranges
rangevals = snd <$> ranges
-- now we zip back the rangekeys so we know which is which
Expand All @@ -121,30 +189,41 @@ main = do
(Map.fromList $ (\(a,b) -> mkFSFD a (fromIntegral b)) <$> eachthing)
(Map.fromList $ (\(a,b) -> mkFSFD a ((read b)::Double)) <$> plainArgs) )
let myenv = (Env Nothing scenario variables_dict)
let answer = runScenario myenv goalname
return $ Answer scenario answer $ eachthing ++ pure ("goal", (round ((read answer)::Double))::Int)
-- return $ (scenario, answer)
-- mapM_ putStrLn (details <$> output)
let mymatrix = Data.Matrix.fromLists $ ((fmap snd) . details) <$> output

case length ranges of
-- data table format. each details contains exactly three elements: the x, the y, and the answer-goal.
2 ->
let answer = runScenario myenv goalexpr
return $ Answer scenario answer $ eachthing ++ pure ("goal", (round ((read $ Text.unpack answer)::Double))::Int)
-- the scenario overlaps with details. this is intentional: the details are the things that range, that we want to show in the table.

let mymatrix = Data.Matrix.fromLists $ ((fmap snd) . details) <$> answers

when (styleval == Just VYAML) $ putStrLn $ concat $ do
answer <- answers
let scenario = scn answer
return $ dumpYAML scenario (Text.pack $ show $ fromJust (lookup "goal" $ details answer))

-- - name: Someone earning 32103 with no dependants and rates of 2000
-- period: 2018
-- absolute_error_margin: 1
-- input:
-- rates_rebates__combined_income: 32103
-- rates_rebates__dependants: 0
-- rates_rebates__rates_total: 2000
-- output:
-- rates_rebates__rebate: 312.67

when (styleval /= Just VYAML) $ case length ranges of
2 -> -- data table format. each details contains exactly three elements: the x, the y, and the answer-goal.
-- coltitles go across the top, but in practice these get glued on top of each individual column of answers, so we don't fold-join them here just yet
let rowtitles = (text "") : ((text . show) <$> (nub $ snd <$> (!! 1) <$> (details <$> output)))
let rowtitles = (text "") : ((text . show) <$> (nub $ snd <$> (!! 1) <$> (details <$> answers)))
-- rowtitles go on the left
coltitles = (text . show) <$> (nub $ snd <$> (!! 0) <$> (details <$> output))
datacols = Data.List.foldl (/>/) nullBox <$> chunksOf (length rowtitles - 1) ((text . show) <$> (snd <$> (!! 2) <$> (details <$> output)))
-- headeredcols = (\datarows -> Data.List.foldl (/>/) nullBox $ Data.List.zipWith (/>/) coltitles datarows) <$> datacols
-- in surround $ Data.List.foldl (Box.<+>) nullBox (Data.List.foldl (/>/) nullBox coltitles : headeredcols)
-- full detail format
coltitles = (text . show) <$> (nub $ snd <$> (!! 0) <$> (details <$> answers))
datacols = Data.List.foldl (/>/) nullBox <$> chunksOf (length rowtitles - 1) ((text . show) <$> (snd <$> (!! 2) <$> (details <$> answers)))
in prettyPrintBox coltitles (Data.List.foldl (/>/) nullBox rowtitles) datacols
_ ->
let colnames = (text . fst) <$> (details $ head output)
_ -> -- ordinary "decision table"
let colnames = (text . fst) <$> (details $ head answers)
datacols = fmap (\col -> Data.List.foldl (/>/) nullBox (fmap (text . show) col)) (Data.Matrix.toLists $ Data.Matrix.transpose mymatrix)
in prettyPrintBox colnames nullBox datacols
-- mapM_ putStrLn (details <$> output)
putStrLn $ "## done with run; " ++ (show $ length output) ++ " answers across " ++ ( Data.List.intercalate " * " $ (\(rk, myr) -> (show $ length $ myr) ++ " variations of " ++ rk) <$> ranges )

-- putStrLn $ "## " ++ (show $ length answers) ++ " answers across " ++ ( Data.List.intercalate " * " $ (\(rk, myr) -> (show $ length $ myr) ++ " variations of " ++ rk) <$> ranges )

where
wantgoal arg = case arg of
Expand All @@ -153,14 +232,31 @@ main = do
getgoal goalarg = case goalarg of
(Just (Goal goal)) -> goal
_ -> (error $ "specify a goal name with --goal=mygoalname; choose one of " ++ show (Map.keys goals))
parseRange :: String -> [Int]
parseRange x = read <$> Main.splitOn ",|\\.\\." x
parseRange :: String -> Maybe [Maybe Int]
parseRange x = (\ms -> readMaybe <$> [ms !! 0, ms !! 2, ms !! 4])
<$> (matchRegex (mkRegex "([0-9]+)(,([0-9]+))?(\\.\\.([0-9]+))?") x)

prettyPrintBox toprow leftcol datacols =
let
headeredcols = Data.List.zipWith (/>/) toprow datacols
tablerows = Data.List.foldl (Box.<+>) leftcol headeredcols
in printBox $ surround tablerows

dumpYAML scenario goalvalue = unlines $ do
let unfd = floor . (\(FD y) -> y) . fromJust
[unwords ["- name: Someone"
,"with " ++ (show $ unfd $ Map.lookup (FS "dependants") scenario) ++ " dependants"
,"earning"
,"$" ++ (show $ unfd $ Map.lookup (FS "combined_income") scenario)
,"who paid $" ++ (show $ unfd $ Map.lookup (FS "rates_total") scenario) ++ " in rates"
]]
++ [" period: " ++ (show $ unfd $ Map.lookup (FS "period") scenario)
," absolute_error_margin: 1"
," input:" ]
++ [ " rates_rebates__" ++ varname ++ ": " ++ (show $ unfd $ Map.lookup (FS $ Text.pack varname) scenario)
| varname <- words "combined_income dependants rates_total" ]
++ [" output:"
," rates_rebates__rebate: " ++ (Text.unpack goalvalue)
]

-- | Paste two boxes together vertically, using a default (left)
-- alignment.
Expand All @@ -169,7 +265,7 @@ t />/ b = vcat right [t,b]


data Answer = Answer { scn :: RatesRebateWorld
, ans :: String
, ans :: Text.Text
, details :: [(String,Int)]
}

Expand All @@ -187,9 +283,43 @@ hDiv n = hcat left (replicate n (char '-'))

surround :: Box -> Box
surround box = let r = rows box
c = cols box + 1
c = cols box + 2
in (char '+' Box.<> hDiv c Box.<> char '+')
// (vDiv r Box.<> box Box.<+> vDiv r )
// (vDiv r Box.<+> box Box.<+> vDiv r )
// (char '+' Box.<> hDiv c Box.<> char '+')


-- 17:43 < freeside> question. I have a list of string infixes that i want to find in a string: ["/",":",".."] `areInfixesOf` "/some/file/path". if i were
-- working against a list of filepaths, I could isInfixOf <$> infixlist <*> pathlist. But is there some idiomatic way to just search
-- against a single filepath rather than a list of filepaths? hoogle returns "liftOp" for a type search for (a -> b -> c) -> [a] -> b ->
-- [c]
-- 17:44 < freeside> I plan to Data.List.or the [c] which is [Bool] to see if any of the infixes matched
-- 17:46 < Solonarv> > map (\i -> i `isInfixOf` "/some/file/path") ["/",":",".."]
-- 17:46 < lambdabot> [True,False,False]
-- 17:46 < freeside> is there some idiomatic way to do it without the lambda?
-- 17:46 < freeside> some sort of punctuation inside < >
-- 17:46 < Solonarv> yes, using an operator section:
-- 17:46 < Solonarv> > any (`isInfixOf` "/some/file/path") ["/",":",".."]
-- 17:46 < lambdabot> True
-- 17:47 < freeside> ah, thank you
-- 17:47 < Solonarv> note: any f xs = or (map f xs)
-- 17:49 < freeside> what if i want to move things around so that the "/some/file/path" would sit at the rightmost end of the function definition? i believe
-- i am groping toward something like point-free style
-- 17:49 < [Leary]> > or $ isInfixOf <$> ["/",":",".."] <*> pure "/some/file/path"
-- 17:49 < lambdabot> True
-- 17:49 < Solonarv> @pl any (`isInfixOf` "/some/file/path") ["/",":",".."]
-- 17:50 < lambdabot> any (`isInfixOf` "/some/file/path") ["/", ":", ".."]
-- 17:50 < Solonarv> oh, right
-- 17:50 < Solonarv> @pl \needles hay -> any (`isInfixOf` hay) needles
-- 17:50 < lambdabot> flip (any . flip isInfixOf)
-- 17:50 < freeside> so the pure squishes my single argument into an invisible list so we can use <*>
-- 17:50 < Solonarv> :D
-- 17:51 < Solonarv> not an "invisible list", just a one-element list
-- 17:51 < Solonarv> pure "path" here is the same as ["path"]
-- 17:51 < freeside> gotcha
-- 17:52 < kuribas> freeside: pointless isn't idiomatic
-- 17:52 < freeside> i was poking around and found (??) in Lens
-- 17:52 < Solonarv> :t (??)
-- 17:53 < lambdabot> Functor f => f (a -> b) -> a -> f b
-- 17:53 < kuribas> freeside: and never use the function (reader) monad, unless you want to obfuscate
-- 17:53 < kuribas> deliberately
2 changes: 2 additions & 0 deletions l4/mkyamls
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
stack exec aotearoa-exe -- additional_per_dependant=500 initial_contribution=160 maximum_allowable=630 income_threshold=25180 period=2019 combined_income=8000,10000..30000 rates_total=120,140..2000 dependants=0..3 --goal=rr-br3nda-clip --nlgstyle=yaml > ~/src/l/openfisca-aotearoa/openfisca_aotearoa/tests/rates_rebates/rates_rebates_2019_legalese.yaml
stack exec aotearoa-exe -- additional_per_dependant=500 initial_contribution=160 maximum_allowable=620 income_threshold=24790 period=2018 combined_income=8000,10000..30000 rates_total=120,140..2000 dependants=0..3 --goal=rr-br3nda-clip --nlgstyle=yaml > ~/src/l/openfisca-aotearoa/openfisca_aotearoa/tests/rates_rebates/rates_rebates_2018_legalese.yaml
Loading

0 comments on commit 1d346f1

Please sign in to comment.