{-# LANGUAGE ImportQualifiedPost #-} {-# LANGUAGE NumericUnderscores #-} {-# LANGUAGE OverloadedStrings #-} module Tax.Canada.Province.BC.BC479.FieldNames (bc479Fields) where import Data.Fixed (Centi) import Rank2 qualified import Tax.Canada.Province.BC.BC479.Types import Tax.Canada.Shared (subCalculationFields) import Tax.FDF (Entry (Amount, Checkbox, Constant, Count, Percent, Textual), FieldConst (Field), within) bc479Fields :: BC479 FieldConst bc479Fields = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "form1" (forall {a}. FieldConst a -> FieldConst a) -> BC479 FieldConst -> BC479 FieldConst forall {k} (g :: (k -> *) -> *) (p :: k -> *) (q :: k -> *). Functor g => (forall (a :: k). p a -> q a) -> g p -> g q forall (p :: * -> *) (q :: * -> *). (forall a. p a -> q a) -> BC479 p -> BC479 q Rank2.<$> BC479 { page1 :: Page1 FieldConst page1 = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Page1" (forall {a}. FieldConst a -> FieldConst a) -> Page1 FieldConst -> Page1 FieldConst forall {k} (g :: (k -> *) -> *) (p :: k -> *) (q :: k -> *). Functor g => (forall (a :: k). p a -> q a) -> g p -> g q forall (p :: * -> *) (q :: * -> *). (forall a. p a -> q a) -> Page1 p -> Page1 q Rank2.<$> Page1 FieldConst page1Fields, page2 :: Page2 FieldConst page2 = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Page2" (forall {a}. FieldConst a -> FieldConst a) -> Page2 FieldConst -> Page2 FieldConst forall {k} (g :: (k -> *) -> *) (p :: k -> *) (q :: k -> *). Functor g => (forall (a :: k). p a -> q a) -> g p -> g q forall (p :: * -> *) (q :: * -> *). (forall a. p a -> q a) -> Page2 p -> Page2 q Rank2.<$> Page2 FieldConst page2Fields, page3 :: Page3 FieldConst page3 = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Page3" (forall {a}. FieldConst a -> FieldConst a) -> Page3 FieldConst -> Page3 FieldConst forall {k} (g :: (k -> *) -> *) (p :: k -> *) (q :: k -> *). Functor g => (forall (a :: k). p a -> q a) -> g p -> g q forall (p :: * -> *) (q :: * -> *). (forall a. p a -> q a) -> Page3 p -> Page3 q Rank2.<$> Page3 FieldConst page3Fields} page1Fields :: Page1 FieldConst page1Fields = Page1 { line1_netIncome_self :: FieldConst Centi line1_netIncome_self = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Chart", Text "Line1", Text "NumWithoutCurrency"] Entry Centi Amount, line1_netIncome_spouse :: FieldConst Centi line1_netIncome_spouse = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Chart", Text "Line1", Text "NumWithoutCurrency2"] Entry Centi Amount, line2_uccb_rdsp_repayment_self :: FieldConst Centi line2_uccb_rdsp_repayment_self = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Chart", Text "Line2", Text "Col1_Amount"] Entry Centi Amount, line2_uccb_rdsp_repayment_spouse :: FieldConst Centi line2_uccb_rdsp_repayment_spouse = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Chart", Text "Line2", Text "Col2_Amount"] Entry Centi Amount, line3_sum_self :: FieldConst Centi line3_sum_self = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Chart", Text "Line3", Text "Col1_Amount"] Entry Centi Amount, line3_sum_spouse :: FieldConst Centi line3_sum_spouse = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Chart", Text "Line3", Text "Col2_Amount"] Entry Centi Amount, line4_uccb_rdsp_income_self :: FieldConst Centi line4_uccb_rdsp_income_self = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Chart", Text "Line4", Text "Col1_Amount"] Entry Centi Amount, line4_uccb_rdsp_income_spouse :: FieldConst Centi line4_uccb_rdsp_income_spouse = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Chart", Text "Line4", Text "Col2_Amount"] Entry Centi Amount, line5_difference_self :: FieldConst Centi line5_difference_self = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Chart", Text "Line5", Text "Col1_Amount"] Entry Centi Amount, line5_difference_spouse :: FieldConst Centi line5_difference_spouse = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Chart", Text "Line5", Text "Col2_Amount"] Entry Centi Amount, line6_sum :: FieldConst Centi line6_sum = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Chart", Text "Line6", Text "Amount"] Entry Centi Amount, line7_threshold :: FieldConst Centi line7_threshold = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line7", Text "Amount"] Entry Centi Amount, line8_difference :: FieldConst Centi line8_difference = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line8", Text "Amount"] Entry Centi Amount, line_60330_sales :: FieldConst Centi line_60330_sales = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line9", Text "Amount"] Entry Centi Amount, line_60350_spouse :: FieldConst Centi line_60350_spouse = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line10", Text "Amount"] Entry Centi Amount, line11_sum :: FieldConst Centi line11_sum = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line11", Text "Amount"] Entry Centi Amount, line12_fraction :: SubCalculation FieldConst line12_fraction = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "Line12" [Text "Amount1"] [Text "Amount2"], line13_difference :: FieldConst Centi line13_difference = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line13", Text "Amount"] Entry Centi Amount, line_60890_separate :: FieldConst Bool line_60890_separate = [Text] -> Entry Bool -> FieldConst Bool forall a. [Text] -> Entry a -> FieldConst a Field [Text "BCSHRTC", Text "Line60890", Text "CheckBox"] Entry Bool Checkbox, line_60480_renovation :: FieldConst Centi line_60480_renovation = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "BCSHRTC", Text "Line14", Text "Line60480", Text "Amount"] Entry Centi Amount, line14_fraction :: FieldConst Centi line14_fraction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "BCSHRTC", Text "Line14", Text "Amount"] Entry Centi Amount, line15_sum :: FieldConst Centi line15_sum = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "BCSHRTC", Text "Line15", Text "Amount"] Entry Centi Amount} page2Fields :: Page2 FieldConst page2Fields = Page2 { line16_copy :: FieldConst Centi line16_copy = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line16", Text "Amount"] Entry Centi Amount, line17_venture :: FieldConst Centi line17_venture = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "BCVCTC", Text "Line17", Text "Amount"] Entry Centi Amount, line_60490_shares :: FieldConst Centi line_60490_shares = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "BCVCTC", Text "Line18", Text "Amount"] Entry Centi Amount, line_60491_certificate :: FieldConst Text line_60491_certificate = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "BCVCTC", Text "Line19", Text "Account_Number_Comb_EN", Text "Account_Number"] Entry Text Textual, line_60495_shares :: FieldConst Centi line_60495_shares = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "BCVCTC", Text "Line20", Text "Amount"] Entry Centi Amount, line_60496_certificate :: FieldConst Text line_60496_certificate = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "BCVCTC", Text "Line21", Text "Account_Number"] Entry Text Textual, line22_sum :: SubCalculation FieldConst line22_sum = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "BCVCTC" [Text "Line22", Text "I1", Text "Amount1"] [Text "Line22", Text "I2", Text "Amount2"], line_60510_fromT88 :: FieldConst Centi line_60510_fromT88 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "BCMETC", Text "Line23", Text "Amount"] Entry Centi Amount, line_60530_fromT88 :: FieldConst Centi line_60530_fromT88 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "BCMETC", Text "Line24", Text "Amount"] Entry Centi Amount, line_60545_buildings :: FieldConst Centi line_60545_buildings = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "BCCBTC", Text "Line25", Text "I1", Text "Amount1"] Entry Centi Amount, line_60546_partnership :: FieldConst Centi line_60546_partnership = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "BCCBTC", Text "Line26", Text "I1", Text "Amount1"] Entry Centi Amount, line27_sum :: SubCalculation FieldConst line27_sum = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "BCCBTC" [Text "Line27", Text "I1", Text "Amount1"] [Text "Line27", Text "I2", Text "Amount2"], line_60550_training :: FieldConst Centi line_60550_training = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "BCTTC", Text "Line28", Text "Amount"] Entry Centi Amount, line_60560_training :: FieldConst Centi line_60560_training = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "BCTTC", Text "Line29", Text "Amount"] Entry Centi Amount, line_60570_ships :: FieldConst Centi line_60570_ships = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "BCTTC", Text "Line30", Text "Amount"] Entry Centi Amount, line31_sum :: SubCalculation FieldConst line31_sum = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "BCTTC" [Text "Line31", Text "I1", Text "Amount1"] [Text "Line31", Text "I2", Text "Amount2"], line32_credits :: FieldConst Centi line32_credits = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "BCTTC", Text "Line32", Text "Amount"] Entry Centi Amount} page3Fields :: Page3 FieldConst page3Fields = Page3 { line33_copy :: FieldConst Centi line33_copy = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line33", Text "Amount"] Entry Centi Amount, tenancy_months1 :: FieldConst Word tenancy_months1 = [Text] -> Entry Word -> FieldConst Word forall a. [Text] -> Entry a -> FieldConst a Field [Text "Declaration-For-Renters", Text "Table", Text "Row1", Text "Numberofmonths"] Entry Word Count, tenancy_months2 :: FieldConst Word tenancy_months2 = [Text] -> Entry Word -> FieldConst Word forall a. [Text] -> Entry a -> FieldConst a Field [Text "Declaration-For-Renters", Text "Table", Text "Row2", Text "Numberofmonths"] Entry Word Count, rent_paid1 :: FieldConst Centi rent_paid1 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Declaration-For-Renters", Text "Table", Text "Row1", Text "Rentpaid"] Entry Centi Amount, rent_paid2 :: FieldConst Centi rent_paid2 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Declaration-For-Renters", Text "Table", Text "Row2", Text "Rentpaid"] Entry Centi Amount, line_60575_sum :: FieldConst Word line_60575_sum = [Text] -> Entry Word -> FieldConst Word forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line34", Text "Amount"] Entry Word Count, line35_ceiling :: FieldConst Centi line35_ceiling = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line35", Text "Amount_ReadOnly"] (Entry Centi -> FieldConst Centi) -> Entry Centi -> FieldConst Centi forall a b. (a -> b) -> a -> b $ Centi -> Entry Centi -> Entry Centi forall a. (Eq a, Show a) => a -> Entry a -> Entry a Constant Centi 400 Entry Centi Amount, line36_income_copy :: FieldConst Centi line36_income_copy = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line36", Text "Amount"] Entry Centi Amount, line37_threshold :: FieldConst Centi line37_threshold = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line37", Text "AmountRead_Only"] (Entry Centi -> FieldConst Centi) -> Entry Centi -> FieldConst Centi forall a b. (a -> b) -> a -> b $ Centi -> Entry Centi -> Entry Centi forall a. (Eq a, Show a) => a -> Entry a -> Entry a Constant Centi 63_000 Entry Centi Amount, line38_difference :: FieldConst Centi line38_difference = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line38", Text "Amount"] Entry Centi Amount, line39_rate :: FieldConst Rational line39_rate = [Text] -> Entry Rational -> FieldConst Rational forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line39", Text "PercentAmount_ReadOnly"] (Entry Rational -> FieldConst Rational) -> Entry Rational -> FieldConst Rational forall a b. (a -> b) -> a -> b $ Rational -> Entry Rational -> Entry Rational forall a. (Eq a, Show a) => a -> Entry a -> Entry a Constant Rational 0.02 Entry Rational Percent, line40_fraction :: SubCalculation FieldConst line40_fraction = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "Line40" [Text "L1", Text "Amount"] [Text "L2", Text "Amount2"], line_60576_difference :: SubCalculation FieldConst line_60576_difference = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "Line41" [Text "I1", Text "Amount1"] [Text "I2", Text "Amount2"], line42_credits :: FieldConst Centi line42_credits = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line42", Text "Amount"] Entry Centi Amount}