{-# LANGUAGE ImportQualifiedPost #-} {-# LANGUAGE DisambiguateRecordFields #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NumericUnderscores #-} {-# LANGUAGE OverloadedStrings #-} module Tax.Canada.Province.AB.AB428.FieldNames (ab428Fields) where import Data.Fixed (Centi) import Data.Text (Text) import Rank2 qualified import Tax.Canada.Province.AB.AB428.Types import Tax.Canada.Shared (BaseCredit(..), MedicalExpenses(..), TaxIncomeBracket (..), subCalculationFields) import Tax.FDF (Entry (Count, Constant, Amount, Percent), FieldConst (Field, NoField), within) ab428Fields :: AB428 FieldConst ab428Fields = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "form1" (forall {a}. FieldConst a -> FieldConst a) -> AB428 FieldConst -> AB428 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) -> AB428 p -> AB428 q Rank2.<$> AB428 { 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 { income :: FieldConst Centi income = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line1", Text "Amount"] Entry Centi Amount, partA :: Page1PartA FieldConst partA = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Chart" (forall {a}. FieldConst a -> FieldConst a) -> Page1PartA FieldConst -> Page1PartA 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) -> Page1PartA p -> Page1PartA q Rank2.<$> Page1PartA FieldConst page1PartAFields, partB :: Page1PartB FieldConst partB = Page1PartB FieldConst page1PartBFields} page1PartAFields :: Page1PartA FieldConst page1PartAFields = Page1PartA { column1 :: TaxIncomeBracket FieldConst column1 = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Column1" (forall {a}. FieldConst a -> FieldConst a) -> TaxIncomeBracket FieldConst -> TaxIncomeBracket 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) -> TaxIncomeBracket p -> TaxIncomeBracket q Rank2.<$> Text -> Centi -> Rational -> Centi -> TaxIncomeBracket FieldConst taxIncomeBracketFields Text "1" Centi 0 Rational 0.10 Centi 0, column2 :: TaxIncomeBracket FieldConst column2 = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Column2" (forall {a}. FieldConst a -> FieldConst a) -> TaxIncomeBracket FieldConst -> TaxIncomeBracket 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) -> TaxIncomeBracket p -> TaxIncomeBracket q Rank2.<$> Text -> Centi -> Rational -> Centi -> TaxIncomeBracket FieldConst taxIncomeBracketFields Text "2" Centi 148_269 Rational 0.12 Centi 14_826.90, column3 :: TaxIncomeBracket FieldConst column3 = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Column3" (forall {a}. FieldConst a -> FieldConst a) -> TaxIncomeBracket FieldConst -> TaxIncomeBracket 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) -> TaxIncomeBracket p -> TaxIncomeBracket q Rank2.<$> (Text -> Centi -> Rational -> Centi -> TaxIncomeBracket FieldConst taxIncomeBracketFields Text "3" Centi 177_922 Rational 0.13 Centi 18_385.26){rate = Field ["LIne5-C3", "Percent"] $ Constant 0.13 Percent}, column4 :: TaxIncomeBracket FieldConst column4 = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Column4" (forall {a}. FieldConst a -> FieldConst a) -> TaxIncomeBracket FieldConst -> TaxIncomeBracket 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) -> TaxIncomeBracket p -> TaxIncomeBracket q Rank2.<$> Text -> Centi -> Rational -> Centi -> TaxIncomeBracket FieldConst taxIncomeBracketFields Text "4" Centi 237_230 Rational 0.14 Centi 26_095.30, column5 :: TaxIncomeBracket FieldConst column5 = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Column5" (forall {a}. FieldConst a -> FieldConst a) -> TaxIncomeBracket FieldConst -> TaxIncomeBracket 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) -> TaxIncomeBracket p -> TaxIncomeBracket q Rank2.<$> Text -> Centi -> Rational -> Centi -> TaxIncomeBracket FieldConst taxIncomeBracketFields Text "5" Centi 355_845 Rational 0.15 Centi 42_701.40} taxIncomeBracketFields :: Text -> Centi -> Rational -> Centi -> TaxIncomeBracket FieldConst taxIncomeBracketFields :: Text -> Centi -> Rational -> Centi -> TaxIncomeBracket FieldConst taxIncomeBracketFields Text column Centi threshold Rational rate Centi baseTax = TaxIncomeBracket { income :: FieldConst Centi income = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line2-C" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text column , Text "Amount"] Entry Centi Amount, threshold :: FieldConst Centi threshold = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line3-C" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text column, Text "Amount"] (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 threshold Entry Centi Amount, overThreshold :: FieldConst Centi overThreshold = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line4-C" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text column, Text "Amount"] Entry Centi Amount, rate :: FieldConst Rational rate = [Text] -> Entry Rational -> FieldConst Rational forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line5-C" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text column, Text "Percent"] (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 rate Entry Rational Percent, timesRate :: FieldConst Centi timesRate = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line6-C" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text column, Text "Amount"] Entry Centi Amount, baseTax :: FieldConst Centi baseTax = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line7-C" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text column, Text "Amount"] (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 baseTax Entry Centi Amount, equalsTax :: FieldConst Centi equalsTax = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line8-C" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text column, Text "Amount"] Entry Centi Amount} page1PartBFields :: Page1PartB FieldConst page1PartBFields = Page1PartB { line9_basic :: FieldConst Centi line9_basic = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line9", Text "Amount"] Entry Centi Amount, line10_age :: FieldConst Centi line10_age = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line10", Text "Amount"] Entry Centi Amount, spouseAmount :: BaseCredit FieldConst spouseAmount = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Spouse-Net-Income" (forall {a}. FieldConst a -> FieldConst a) -> BaseCredit FieldConst -> BaseCredit 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) -> BaseCredit p -> BaseCredit q Rank2.<$> BaseCredit{ baseAmount :: FieldConst Centi baseAmount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line11", Text "Amount"] (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 21_885 Entry Centi Amount, reduction :: FieldConst Centi reduction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line12", Text "Amount"] Entry Centi Amount, difference :: FieldConst Centi difference = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line13", Text "Amount1"] Entry Centi Amount, cont :: FieldConst Centi cont = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line13", Text "Amount2"] Entry Centi Amount}, dependantAmount :: BaseCredit FieldConst dependantAmount = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Eligible-Dependant" (forall {a}. FieldConst a -> FieldConst a) -> BaseCredit FieldConst -> BaseCredit 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) -> BaseCredit p -> BaseCredit q Rank2.<$> BaseCredit{ baseAmount :: FieldConst Centi baseAmount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line14", Text "Amount"] (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 21_885 Entry Centi Amount, reduction :: FieldConst Centi reduction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line15", Text "Amount"] Entry Centi Amount, difference :: FieldConst Centi difference = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line16", Text "Amount1"] Entry Centi Amount, cont :: FieldConst Centi cont = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line16", Text "Amount2"] Entry Centi Amount}, line17_infirm :: FieldConst Centi line17_infirm = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line17", Text "Amount"] Entry Centi Amount, line18 :: FieldConst Centi line18 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line18", Text "Amount"] Entry Centi Amount, line19_cppQpp :: FieldConst Centi line19_cppQpp = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "CPP-QPP", Text "Line19", Text "Amount"] Entry Centi Amount, line20_cppQpp :: FieldConst Centi line20_cppQpp = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "CPP-QPP", Text "Line20", Text "Amount"] Entry Centi Amount, line21_employmentInsurance :: FieldConst Centi line21_employmentInsurance = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "EI", Text "Line21", Text "Amount"] Entry Centi Amount, line22_employmentInsurance :: FieldConst Centi line22_employmentInsurance = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "EI", Text "Line22", Text "Amount"] Entry Centi Amount, line23_adoption :: FieldConst Centi line23_adoption = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line23", Text "Amount"] Entry Centi Amount, line24_sum :: SubCalculation FieldConst line24_sum = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "Line24" [Text "Amount1"] [Text "Amount2"], line25 :: FieldConst Centi line25 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line25", Text "Amount"] Entry Centi Amount} page2Fields :: Page2 FieldConst page2Fields = Page2 { partB :: Page2PartB FieldConst partB = Page2PartB FieldConst page2PartBFields} page2PartBFields :: Page2PartB FieldConst page2PartBFields = Page2PartB { line26 :: FieldConst Centi line26 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line26", Text "Amount"] Entry Centi Amount, line27_pension :: FieldConst Centi line27_pension = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line27", Text "Amount"] Entry Centi Amount, line28_caregiver :: FieldConst Centi line28_caregiver = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line28", Text "Amount"] Entry Centi Amount, line29 :: FieldConst Centi line29 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line29", Text "Amount"] Entry Centi Amount, line30_disability :: FieldConst Centi line30_disability = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line30", Text "Amount"] Entry Centi Amount, line31 :: FieldConst Centi line31 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line31", Text "Amount"] Entry Centi Amount, line32 :: FieldConst Centi line32 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line32", Text "Amount"] Entry Centi Amount, line33_interest :: FieldConst Centi line33_interest = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line33", Text "Amount"] Entry Centi Amount, line34_education :: FieldConst Centi line34_education = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line34", Text "Amount"] Entry Centi Amount, line35_transferredSpouse :: FieldConst Centi line35_transferredSpouse = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line35", Text "Amount"] Entry Centi Amount, line36 :: FieldConst Centi line36 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line36", Text "Amount"] Entry Centi Amount, medicalExpenses :: MedicalExpenses FieldConst medicalExpenses = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Medical-Expenses" (forall {a}. FieldConst a -> FieldConst a) -> MedicalExpenses FieldConst -> MedicalExpenses 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) -> MedicalExpenses p -> MedicalExpenses q Rank2.<$> MedicalExpenses FieldConst medicalExpensesFields, line43 :: FieldConst Centi line43 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line43", Text "Amount"] Entry Centi Amount, line44_sum :: SubCalculation FieldConst line44_sum = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "Line44" [Text "Amount1"] [Text "Amount2"], line45 :: FieldConst Centi line45 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line45", Text "Amount"] Entry Centi Amount, line46_rate :: FieldConst Rational line46_rate = [Text] -> Entry Rational -> FieldConst Rational forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line46", Text "Percent"] (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.10 Entry Rational Percent, line47_fraction :: FieldConst Centi line47_fraction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line47", Text "Amount"] Entry Centi Amount, donations :: Donations FieldConst donations = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Donation-Gift" (forall {a}. FieldConst a -> FieldConst a) -> Donations FieldConst -> Donations 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) -> Donations p -> Donations q Rank2.<$> Donations FieldConst donationFields, line50_sum :: SubCalculation FieldConst line50_sum = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "Line50" [Text "Amount1"] [Text "Amount2"], line51 :: FieldConst Centi line51 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line51", Text "Amount"] Entry Centi Amount} medicalExpensesFields :: MedicalExpenses FieldConst medicalExpensesFields = MedicalExpenses { expenses :: FieldConst Centi expenses = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line37", Text "Amount"] Entry Centi Amount, netIncome :: FieldConst Centi netIncome = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line38", Text "Amount"] Entry Centi Amount, incomeRate :: FieldConst Rational incomeRate = [Text] -> Entry Rational -> FieldConst Rational forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line39", Text "Percent"] (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.03 Entry Rational Percent, fraction :: FieldConst Centi fraction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line40", Text "Amount"] Entry Centi Amount, lesser :: FieldConst Centi lesser = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line41", Text "Amount"] Entry Centi Amount, difference :: FieldConst Centi difference = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line42", Text "Amount"] Entry Centi Amount} donationFields :: Donations FieldConst donationFields = Donations { line48_base :: FieldConst Centi line48_base = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line48", Text "Amount1"] Entry Centi Amount, line48_fraction :: FieldConst Centi line48_fraction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line48", Text "Amount2"] Entry Centi Amount, line49_base :: FieldConst Centi line49_base = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line49", Text "Amount1"] Entry Centi Amount, line49_fraction :: FieldConst Centi line49_fraction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line49", Text "Amount2"] Entry Centi Amount} page3Fields :: Page3 FieldConst page3Fields = Page3 { partC :: PartC FieldConst partC = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "PartC" (forall {a}. FieldConst a -> FieldConst a) -> PartC FieldConst -> PartC 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) -> PartC p -> PartC q Rank2.<$> PartC FieldConst partCFields} partCFields :: PartC FieldConst partCFields = PartC { line52_tax :: FieldConst Centi line52_tax = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line52", Text "Amount"] Entry Centi Amount, line53_splitIncomeTax :: FieldConst Centi line53_splitIncomeTax = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line53", Text "Amount"] Entry Centi Amount, line54 :: FieldConst Centi line54 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line54", Text "Amount"] Entry Centi Amount, line55_copy :: FieldConst Centi line55_copy = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line55", Text "Amount"] Entry Centi Amount, line56_dividendCredits :: FieldConst Centi line56_dividendCredits = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line56", Text "Amount"] Entry Centi Amount, line57_copy :: FieldConst Centi line57_copy = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line57", Text "Amount1"] Entry Centi Amount, line57_fraction :: FieldConst Centi line57_fraction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line57", Text "Amount2"] Entry Centi Amount, line58_sum :: SubCalculation FieldConst line58_sum = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "Line58" [Text "Amount1"] [Text "Amount2"], line59_difference :: FieldConst Centi line59_difference = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line59", Text "Amount"] Entry Centi Amount, line60_fromT691 :: FieldConst Centi line60_fromT691 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line60", Text "Amount1"] Entry Centi Amount, line60_fraction :: FieldConst Centi line60_fraction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line60", Text "Amount2"] Entry Centi Amount, line61 :: FieldConst Centi line61 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line61", Text "Amount"] Entry Centi Amount, line62_foreignCredit :: FieldConst Centi line62_foreignCredit = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line62", Text "Amount"] Entry Centi Amount, line63_difference :: FieldConst Centi line63_difference = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line63", Text "Amount"] Entry Centi Amount, line64_political :: FieldConst Centi line64_political = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line64", Text "Amount"] Entry Centi Amount, line65_political :: FieldConst Centi line65_political = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line65", Text "Amount"] Entry Centi Amount, line66_tax :: FieldConst Centi line66_tax = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line66", Text "Amount"] Entry Centi Amount}