{-# LANGUAGE ImportQualifiedPost #-} {-# LANGUAGE DisambiguateRecordFields #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NumericUnderscores #-} {-# LANGUAGE OverloadedStrings #-} module Tax.Canada.T1.FieldNames.ON where import Rank2 qualified import Data.Text (Text) import Data.Text.Lazy (toStrict) import Data.Text.Lazy.Builder (fromText, toLazyText) import Data.Text.Lazy.Builder.Int (decimal) import Tax.FDF (FieldConst (Field, NoField), Entry (..), within) import Tax.Canada.Shared (TaxIncomeBracket (..), subCalculationFields) import Tax.Canada.T1.Types t1Fields :: T1 FieldConst t1Fields :: T1 FieldConst t1Fields = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "form1" (forall {a}. FieldConst a -> FieldConst a) -> T1 FieldConst -> T1 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) -> T1 p -> T1 q Rank2.<$> T1 { page1 :: Page1 FieldConst page1 = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Page1" (FieldConst a -> FieldConst a) -> (FieldConst a -> FieldConst a) -> FieldConst a -> FieldConst a forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Return-pg1" (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" (FieldConst a -> FieldConst a) -> (FieldConst a -> FieldConst a) -> FieldConst a -> FieldConst a forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Return-pg3" (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, page4 :: Page4 FieldConst page4 = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Page4" (FieldConst a -> FieldConst a) -> (FieldConst a -> FieldConst a) -> FieldConst a -> FieldConst a forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Return-pg4" (forall {a}. FieldConst a -> FieldConst a) -> Page4 FieldConst -> Page4 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) -> Page4 p -> Page4 q Rank2.<$> Page4 FieldConst page4Fields, page5 :: Page5 FieldConst page5 = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Page5" (FieldConst a -> FieldConst a) -> (FieldConst a -> FieldConst a) -> FieldConst a -> FieldConst a forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Return-pg5" (forall {a}. FieldConst a -> FieldConst a) -> Page5 FieldConst -> Page5 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) -> Page5 p -> Page5 q Rank2.<$> Page5 FieldConst page5Fields, page6 :: Page6 FieldConst page6 = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Page6" (FieldConst a -> FieldConst a) -> (FieldConst a -> FieldConst a) -> FieldConst a -> FieldConst a forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Return-pg6" (FieldConst a -> FieldConst a) -> (FieldConst a -> FieldConst a) -> FieldConst a -> FieldConst a forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "PartB" (forall {a}. FieldConst a -> FieldConst a) -> Page6 FieldConst -> Page6 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) -> Page6 p -> Page6 q Rank2.<$> Page6 FieldConst page6Fields, page7 :: Page7 FieldConst page7 = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Page7" (FieldConst a -> FieldConst a) -> (FieldConst a -> FieldConst a) -> FieldConst a -> FieldConst a forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Return-pg7" (forall {a}. FieldConst a -> FieldConst a) -> Page7 FieldConst -> Page7 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) -> Page7 p -> Page7 q Rank2.<$> Page7 FieldConst page7Fields, page8 :: Page8 FieldConst page8 = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Page8" (forall {a}. FieldConst a -> FieldConst a) -> Page8 FieldConst -> Page8 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) -> Page8 p -> Page8 q Rank2.<$> Page8 FieldConst page8Fields} page1Fields :: Page1 FieldConst page1Fields = Page1 { identification :: Identification FieldConst identification = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Identification" (forall {a}. FieldConst a -> FieldConst a) -> Identification FieldConst -> Identification 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) -> Identification p -> Identification q Rank2.<$> Identification FieldConst page1IdentificationFields, residence :: Residence FieldConst residence = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Residence_Info" (forall {a}. FieldConst a -> FieldConst a) -> Residence FieldConst -> Residence 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) -> Residence p -> Residence q Rank2.<$> Residence FieldConst page1ResidenceFields, spouse :: Spouse FieldConst spouse = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Info_Spouse_CLP" (forall {a}. FieldConst a -> FieldConst a) -> Spouse FieldConst -> Spouse 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) -> Spouse p -> Spouse q Rank2.<$> Spouse FieldConst page1SpouseFields} page1IdentificationFields :: Identification FieldConst page1IdentificationFields = Identification { emailAddress :: FieldConst Text emailAddress = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "EmailAddress"] Entry Text Textual, dateDeath :: FieldConst Day dateDeath = [Text] -> Entry Day -> FieldConst Day forall a. [Text] -> Entry a -> FieldConst a Field [Text "DateDeath_Comb_BordersAll", Text "DateDeath_Comb"] Entry Day Date, postalCode :: FieldConst Text postalCode = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "PostalCode_Comb_BordersAll", Text "PostalCode"] Entry Text Textual, your_Language :: FieldConst LanguageOfCorrespondence your_Language = [Text] -> Entry LanguageOfCorrespondence -> FieldConst LanguageOfCorrespondence forall a. [Text] -> Entry a -> FieldConst a Field [Text "Your_Language", Text "RadioButtonlanguaget"] (Entry LanguageOfCorrespondence -> FieldConst LanguageOfCorrespondence) -> Entry LanguageOfCorrespondence -> FieldConst LanguageOfCorrespondence forall a b. (a -> b) -> a -> b $ [LanguageOfCorrespondence] -> Entry LanguageOfCorrespondence forall a. (Eq a, Show a) => [a] -> Entry a RadioButton [LanguageOfCorrespondence English, LanguageOfCorrespondence French], id_City :: FieldConst Text id_City = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "ID_City"] Entry Text Textual, sin :: FieldConst Text sin = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "SIN_Comb_BordersAll", Text "SIN_Comb"] Entry Text Textual, id_LastName :: FieldConst Text id_LastName = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "ID_LastName"] Entry Text Textual, dateBirth :: FieldConst Day dateBirth = [Text] -> Entry Day -> FieldConst Day forall a. [Text] -> Entry a -> FieldConst a Field [Text "DateBirth_Comb_BordersAll", Text "DateBirth_Comb"] Entry Day Date, id_FirstNameInitial :: FieldConst Text id_FirstNameInitial = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "ID_FirstNameInitial"] Entry Text Textual, id_MailingAddress :: FieldConst Text id_MailingAddress = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "ID_MailingAddress"] Entry Text Textual, maritalStatus :: FieldConst MaritalStatus maritalStatus = [Text] -> Entry MaritalStatus -> FieldConst MaritalStatus forall a. [Text] -> Entry a -> FieldConst a Field [Text "MaritalStatus_Checkbox"] (Entry MaritalStatus -> FieldConst MaritalStatus) -> Entry MaritalStatus -> FieldConst MaritalStatus forall a b. (a -> b) -> a -> b $ Int -> Int -> Text -> [MaritalStatus] -> Entry MaritalStatus forall a. (Bounded a, Enum a, Eq a, Show a) => Int -> Int -> Text -> [a] -> Entry a RadioButtons Int 0 Int 1 Text "MaritalStatus" [MaritalStatus Married .. MaritalStatus Single], id_RuralRoute :: FieldConst Text id_RuralRoute = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "ID_RuralRoute"] Entry Text Textual, id_POBox :: FieldConst Text id_POBox = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "ID_POBox"] Entry Text Textual, prov_DropDown :: FieldConst Code prov_DropDown = [Text] -> Entry Code -> FieldConst Code forall a. [Text] -> Entry a -> FieldConst a Field [Text "Prov_DropDown"] Entry Code Province} page1ResidenceFields :: Residence FieldConst page1ResidenceFields = Residence { prov_DropDown_Business :: FieldConst Code prov_DropDown_Business = [Text] -> Entry Code -> FieldConst Code forall a. [Text] -> Entry a -> FieldConst a Field [Text "Prov_DropDown-Business"] Entry Code Province, prov_DropDown_Residence :: FieldConst Code prov_DropDown_Residence = [Text] -> Entry Code -> FieldConst Code forall a. [Text] -> Entry a -> FieldConst a Field [Text "Prov_DropDown-Residence"] Entry Code Province, date_Departure :: FieldConst Day date_Departure = [Text] -> Entry Day -> FieldConst Day forall a. [Text] -> Entry a -> FieldConst a Field [Text "Date_Departure", Text "DateMMDD_Comb_BordersAll_Std", Text "DateMMDD_Comb"] Entry Day Date, date_Entry :: FieldConst Day date_Entry = [Text] -> Entry Day -> FieldConst Day forall a. [Text] -> Entry a -> FieldConst a Field [Text "Date_Entry", Text "DateMMDD_Comb_BordersAll_Std", Text "DateMMDD_Comb"] Entry Day Date, prov_DropDown :: FieldConst Text prov_DropDown = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "Prov_DropDown"] Entry Text Textual} page1SpouseFields :: Spouse FieldConst page1SpouseFields = Spouse { line_23600 :: FieldConst Centi line_23600 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line23600", Text "Amount"] Entry Centi Amount, self_employment :: FieldConst Bool self_employment = [Text] -> Entry Bool -> FieldConst Bool forall a. [Text] -> Entry a -> FieldConst a Field [Text "Self-employment", Text "Checkbox"] Entry Bool Checkbox, spouse_First_Name :: FieldConst Text spouse_First_Name = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "Spouse_First_Name"] Entry Text Textual, line_11700 :: FieldConst Centi line_11700 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line11700", Text "Amount"] Entry Centi Amount, line_21300 :: FieldConst Centi line_21300 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line21300", Text "Amount"] Entry Centi Amount, sin :: FieldConst Text sin = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "SIN_Comb_BordersAll", Text "SIN_Comb"] Entry Text Textual} page2Fields :: Page2 FieldConst page2Fields = Page2 { foreign_property :: FieldConst Bool foreign_property = [Text] -> Entry Bool -> FieldConst Bool forall a. [Text] -> Entry a -> FieldConst a Field [Text "Foreign_property", Text "Line26600"] (Entry Bool -> FieldConst Bool) -> Entry Bool -> FieldConst Bool forall a b. (a -> b) -> a -> b $ Text -> Text -> Text -> Entry Bool Switch Text "Option1" Text "Option2" Text "ForeignProperty_CheckBox", tax_exempt :: FieldConst Bool tax_exempt = [Text] -> Entry Bool -> FieldConst Bool forall a. [Text] -> Entry a -> FieldConst a Field [Text "Tax_exempt", Text "Exempt", Text "Spouse_SelfEmployed"] Entry Bool Checkbox, electionsCanada :: ElectionsCanada FieldConst electionsCanada = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "ElectionsCanada" (forall {a}. FieldConst a -> FieldConst a) -> ElectionsCanada FieldConst -> ElectionsCanada 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) -> ElectionsCanada p -> ElectionsCanada q Rank2.<$> ElectionsCanada FieldConst page2ElectionsCanadaFields, cai :: FieldConst Bool cai = [Text] -> Entry Bool -> FieldConst Bool forall a. [Text] -> Entry a -> FieldConst a Field [Text "CAI", Text "CAI_ON", Text "Tick_box"] Entry Bool Checkbox, organ_donor :: FieldConst Bool organ_donor = [Text] -> Entry Bool -> FieldConst Bool forall a. [Text] -> Entry a -> FieldConst a Field [Text "Organ_donor", Text "Question"] (Entry Bool -> FieldConst Bool) -> Entry Bool -> FieldConst Bool forall a b. (a -> b) -> a -> b $ Text -> Text -> Text -> Entry Bool Switch Text "Option1" Text "Option2" Text "OrganDonor_CheckBox" } page2ElectionsCanadaFields :: ElectionsCanada FieldConst page2ElectionsCanadaFields = ElectionsCanada { citizenship :: FieldConst Bool citizenship = [Text] -> Entry Bool -> FieldConst Bool forall a. [Text] -> Entry a -> FieldConst a Field [Text "LineA"] (Entry Bool -> FieldConst Bool) -> Entry Bool -> FieldConst Bool forall a b. (a -> b) -> a -> b $ Text -> Text -> Text -> Entry Bool Switch Text "Option1" Text "Option2" Text "A_CheckBox", authorization :: FieldConst Bool authorization = [Text] -> Entry Bool -> FieldConst Bool forall a. [Text] -> Entry a -> FieldConst a Field [Text "LineB"] (Entry Bool -> FieldConst Bool) -> Entry Bool -> FieldConst Bool forall a b. (a -> b) -> a -> b $ Text -> Text -> Text -> Entry Bool Switch Text "Option1" Text "Option2" Text "B_Authorize_CheckBox"} page3Fields :: Page3 FieldConst page3Fields = Page3 { line_10100_EmploymentIncome :: FieldConst Centi line_10100_EmploymentIncome = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line1", Text "Line_10100_Amount"] Entry Centi Amount, line_10105_Taxexemptamount :: FieldConst Centi line_10105_Taxexemptamount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line10105", Text "Line_10105_Amount"] Entry Centi Amount, line_10120_Commissions :: FieldConst Centi line_10120_Commissions = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line10120", Text "Line_10120_Amount"] Entry Centi Amount, line_10130_sf :: FieldConst Centi line_10130_sf = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line10130", Text "Line_10130_Amount"] Entry Centi Amount, line_10400_OtherEmploymentIncome :: FieldConst Centi line_10400_OtherEmploymentIncome = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line10400", Text "Line_10400_Amount"] Entry Centi Amount, line_11300_OldAgeSecurityPension :: FieldConst Centi line_11300_OldAgeSecurityPension = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line11300", Text "Line_11300_Amount"] Entry Centi Amount, line_11400_CPP_QPP :: FieldConst Centi line_11400_CPP_QPP = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line11400", Text "Line_11400_Amount"] Entry Centi Amount, line_11410_DisabilityBenefits :: FieldConst Centi line_11410_DisabilityBenefits = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line11410", Text "Line_11410_Amount"] Entry Centi Amount, line_11500_OtherPensions :: FieldConst Centi line_11500_OtherPensions = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line11500", Text "Line_11500_Amount"] Entry Centi Amount, line_11600_ElectedSplitPension :: FieldConst Centi line_11600_ElectedSplitPension = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line11600", Text "Line_11600_Amount"] Entry Centi Amount, line_11700_UCCB :: FieldConst Centi line_11700_UCCB = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line11700", Text "Line_11700_Amount"] Entry Centi Amount, line_11701_UCCBDesignated :: FieldConst Centi line_11701_UCCBDesignated = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line11701", Text "Line_11701_Amount"] Entry Centi Amount, line_11900_EmploymentInsurance :: FieldConst Centi line_11900_EmploymentInsurance = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line11900", Text "Line_11900_Amount"] Entry Centi Amount, line_11905_Employmentmaternity :: FieldConst Centi line_11905_Employmentmaternity = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line11905", Text "Line_11905_Amount"] Entry Centi Amount, line_12000_TaxableDividends :: FieldConst Centi line_12000_TaxableDividends = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line12000", Text "Line_12000_Amount"] Entry Centi Amount, line_12010_OtherTaxableDividends :: FieldConst Centi line_12010_OtherTaxableDividends = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line12010", Text "Line_12010_Amount"] Entry Centi Amount, line_12100_InvestmentIncome :: FieldConst Centi line_12100_InvestmentIncome = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line12100", Text "Line_12100_Amount"] Entry Centi Amount, line_12200_PartnershipIncome :: FieldConst Centi line_12200_PartnershipIncome = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line12200", Text "Line_12200_Amount"] Entry Centi Amount, line_12500_RDSP :: FieldConst Centi line_12500_RDSP = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line12500", Text "Line_12500_Amount"] Entry Centi Amount, line_12599_12600_RentalIncome :: FieldConst Centi line_12599_12600_RentalIncome = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line12600", Text "Line12599", Text "Line_12599_Amount"] Entry Centi Amount, line_12600_Amount :: FieldConst Centi line_12600_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line12600", Text "Line_12600_Amount"] Entry Centi Amount, line_12700_TaxableCapitalGains :: FieldConst Centi line_12700_TaxableCapitalGains = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line12700", Text "Line_12700_Amount"] Entry Centi Amount, line_12701_CapitalGainsReduction :: FieldConst Centi line_12701_CapitalGainsReduction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line12701", Text "Line_12701_Amount"] Entry Centi Amount, line16_difference :: SubCalculation FieldConst line16_difference = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "Line16" [Text "Amount1"] [Text "Amount2"], line_12799_Amount :: FieldConst Centi line_12799_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line12800", Text "Line_12799", Text "Line_12799_Amount"] Entry Centi Amount, line_12800_Amount :: FieldConst Centi line_12800_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line12800", Text "Line_12800_Amount"] Entry Centi Amount, line_12900_RRSPIncome :: FieldConst Centi line_12900_RRSPIncome = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line12900", Text "Line_12900_Amount"] Entry Centi Amount, line_12905_FHSAIncome :: FieldConst Centi line_12905_FHSAIncome = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line12905", Text "Line_12905_Amount"] Entry Centi Amount, line_12906_OtherFHSAIncome :: FieldConst Centi line_12906_OtherFHSAIncome = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line12906", Text "Line_12906_Amount"] Entry Centi Amount, line_13000_OtherIncome :: FieldConst Centi line_13000_OtherIncome = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line13000", Text "Line_13000_Amount"] Entry Centi Amount, line_13000_OtherIncomeSource :: FieldConst Text line_13000_OtherIncomeSource = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line13000", Text "Line_13000_Specify"] Entry Text Textual, line_13010_TaxableScholarship :: FieldConst Centi line_13010_TaxableScholarship = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line13010", Text "Line_13010_Amount"] Entry Centi Amount, line23_sum :: FieldConst Centi line23_sum = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line23", Text "Amount"] Entry Centi Amount, selfEmployment :: SelfEmploymentIncome FieldConst selfEmployment = SelfEmploymentIncome FieldConst selfEmploymentFields, line29_sum :: SubCalculation FieldConst line29_sum = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "Line29" [Text "Amount1"] [Text "Amount2"], line30_sum :: FieldConst Centi line30_sum = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line30", Text "Amount"] Entry Centi Amount, line_14400_WorkersCompBen :: FieldConst Centi line_14400_WorkersCompBen = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line14400", Text "Line_14400_Amount"] Entry Centi Amount, line_14500_SocialAssistPay :: FieldConst Centi line_14500_SocialAssistPay = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line14500", Text "Line_14500_Amount"] Entry Centi Amount, line_14600_NetFedSupplements :: FieldConst Centi line_14600_NetFedSupplements = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line14600", Text "Line_14600_Amount"] Entry Centi Amount, line_14700_sum :: SubCalculation FieldConst line_14700_sum = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "Line14700" [Text "Line_14700_Amount1"] [Text "Line_14700_Amount2"], line_15000_TotalIncome :: FieldConst Centi line_15000_TotalIncome = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line15000", Text "Line_15000_Amount"] Entry Centi Amount} selfEmploymentFields :: SelfEmploymentIncome FieldConst selfEmploymentFields = SelfEmploymentIncome { line_13499_Amount :: FieldConst Centi line_13499_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line13500", Text "Line13499", Text "Line_13499_Amount"] Entry Centi Amount, line_13500_Amount :: FieldConst Centi line_13500_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line13500", Text "Line_13500_Amount"] Entry Centi Amount, line_13699_Amount :: FieldConst Centi line_13699_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line13700", Text "Line13699", Text "Line_13699_Amount"] Entry Centi Amount, line_13700_Amount :: FieldConst Centi line_13700_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line13700", Text "Line_13700_Amount"] Entry Centi Amount, line_13899_Amount :: FieldConst Centi line_13899_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line13900", Text "Line13899", Text "Line_13899_Amount"] Entry Centi Amount, line_13900_Amount :: FieldConst Centi line_13900_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line13900", Text "Line_13900_Amount"] Entry Centi Amount, line_14099_Amount :: FieldConst Centi line_14099_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line14100", Text "Line14099", Text "Line_14099_Amount"] Entry Centi Amount, line_14100_Amount :: FieldConst Centi line_14100_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line14100", Text "Line_14100_Amount"] Entry Centi Amount, line_14299_Amount :: FieldConst Centi line_14299_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line14300", Text "Line14299", Text "Line_14299_Amount"] Entry Centi Amount, line_14300_Amount :: FieldConst Centi line_14300_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line14300", Text "Line_14300_Amount"] Entry Centi Amount} page4Fields :: Page4 FieldConst page4Fields = Page4 { line_15000_TotalIncome_2 :: FieldConst Centi line_15000_TotalIncome_2 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line36", Text "Amount"] Entry Centi Amount, line_20600_PensionAdjustment :: FieldConst Centi line_20600_PensionAdjustment = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line20600", Text "Line_20600_Amount"] Entry Centi Amount, line_20700_RPPDeduction :: FieldConst Centi line_20700_RPPDeduction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line20700", Text "Line_20700_Amount"] Entry Centi Amount, line_20800_RRSPDeduction :: FieldConst Centi line_20800_RRSPDeduction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line20800", Text "Line_20800_Amount"] Entry Centi Amount, line_20805_FHSADeduction :: FieldConst Centi line_20805_FHSADeduction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line20805", Text "Line_20805_Amount"] Entry Centi Amount, line_20810_PRPP :: FieldConst Centi line_20810_PRPP = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line20810", Text "Line_20810_Amount"] Entry Centi Amount, line_21000_SplitPensionDeduction :: FieldConst Centi line_21000_SplitPensionDeduction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line21000", Text "Line_21000_Amount"] Entry Centi Amount, line_21200_Dues :: FieldConst Centi line_21200_Dues = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line21200", Text "Line_21200_Amount"] Entry Centi Amount, line_21300_UCCBRepayment :: FieldConst Centi line_21300_UCCBRepayment = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line21300", Text "Line_21300_Amount"] Entry Centi Amount, line_21400_ChildCareExpenses :: FieldConst Centi line_21400_ChildCareExpenses = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line21400", Text "Line_21400_Amount"] Entry Centi Amount, line_21500_DisabilityDeduction :: FieldConst Centi line_21500_DisabilityDeduction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line21500", Text "Line_21500_Amount"] Entry Centi Amount, line_21698_Amount :: FieldConst Centi line_21698_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line45", Text "Line21698", Text "Line_21698_Amount"] Entry Centi Amount, line_21699_Amount :: FieldConst Centi line_21699_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line45", Text "Line21699", Text "Line_21699_Amount"] Entry Centi Amount, line_21700_Amount :: FieldConst Centi line_21700_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line45", Text "Line21700", Text "Line_21900_Amount"] Entry Centi Amount, line_21900_MovingExpenses :: FieldConst Centi line_21900_MovingExpenses = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line21900", Text "Line_21900_Amount"] Entry Centi Amount, line_21999_Amount :: FieldConst Centi line_21999_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line22000", Text "Line21999", Text "Line_21999_Amount"] Entry Centi Amount, line_22000_Amount :: FieldConst Centi line_22000_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line22000", Text "Line_22000_Amount"] Entry Centi Amount, line_22100_CarryingChargesInterest :: FieldConst Centi line_22100_CarryingChargesInterest = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line22100", Text "Line_22100_Amount"] Entry Centi Amount, line_22200_CPP_QPP_Contributions :: FieldConst Centi line_22200_CPP_QPP_Contributions = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line22200", Text "Line_22200_Amount"] Entry Centi Amount, line_22215_DeductionCPP_QPP :: FieldConst Centi line_22215_DeductionCPP_QPP = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line22215", Text "Line_22215_Amount"] Entry Centi Amount, line_22300_DeductionPPIP :: FieldConst Centi line_22300_DeductionPPIP = FieldConst Centi forall a. FieldConst a NoField, line_22400_XplorationDevExpenses :: FieldConst Centi line_22400_XplorationDevExpenses = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line22400", Text "Line_22400_Amount"] Entry Centi Amount, line_22900_OtherEmployExpenses :: FieldConst Centi line_22900_OtherEmployExpenses = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line22900", Text "Line_22900_Amount"] Entry Centi Amount, line_23100_ClergyResDeduction :: FieldConst Centi line_23100_ClergyResDeduction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line23100", Text "Line_23100_Amount"] Entry Centi Amount, line_23200_OtherDeductions :: FieldConst Centi line_23200_OtherDeductions = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line23200", Text "Line_23200_Amount"] Entry Centi Amount, line_23200_Specify :: FieldConst Text line_23200_Specify = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line23200", Text "Line_23200_Specify"] Entry Text Textual, line_23300_sum :: SubCalculation FieldConst line_23300_sum = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "Line23300" [Text "Line_23300_Amount1"] [Text "Line_23300_Amount2"], line_23400_NetBeforeAdjust :: FieldConst Centi line_23400_NetBeforeAdjust = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line23400", Text "Line19Amount"] Entry Centi Amount, line_23500_SocialBenefits :: FieldConst Centi line_23500_SocialBenefits = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line23500", Text "Line_23500_Amount"] Entry Centi Amount, line_23600_NetIncome :: FieldConst Centi line_23600_NetIncome = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line23600", Text "Line_23600_Amount"] Entry Centi Amount} page5Fields :: Page5 FieldConst page5Fields = Page5 { step4_TaxableIncome :: Step4 FieldConst step4_TaxableIncome = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Step4" (forall {a}. FieldConst a -> FieldConst a) -> Step4 FieldConst -> Step4 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) -> Step4 p -> Step4 q Rank2.<$> Step4 FieldConst step4Fields, partA_FederalTax :: Page5PartA FieldConst partA_FederalTax = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "PartA" (forall {a}. FieldConst a -> FieldConst a) -> Page5PartA FieldConst -> Page5PartA 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) -> Page5PartA p -> Page5PartA q Rank2.<$> Text -> Int -> Page5PartA FieldConst partAFields Text "Column" Int 36, partB_FederalTaxCredits :: Page5PartB FieldConst partB_FederalTaxCredits = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "PartB" (forall {a}. FieldConst a -> FieldConst a) -> Page5PartB FieldConst -> Page5PartB 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) -> Page5PartB p -> Page5PartB q Rank2.<$> Page5PartB FieldConst partBFields} step4Fields :: Step4 FieldConst step4Fields = Step4 { line_23600_NetIncome_2 :: FieldConst Centi line_23600_NetIncome_2 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line59", Text "Amount"] Entry Centi Amount, line_24400_MilitaryPoliceDeduction :: FieldConst Centi line_24400_MilitaryPoliceDeduction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line24400", Text "Line_24400_Amount"] Entry Centi Amount, line_24900_SecurityDeductions :: FieldConst Centi line_24900_SecurityDeductions = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line24900", Text "Line_24900_Amount"] Entry Centi Amount, line_24901_SecurityDeductions :: FieldConst Centi line_24901_SecurityDeductions = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line24901", Text "Line_Amount"] Entry Centi Amount, line_25000_OtherPayDeductions :: FieldConst Centi line_25000_OtherPayDeductions = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line25000", Text "Line_25000_Amount"] Entry Centi Amount, line_25100_PartnershipLosses :: FieldConst Centi line_25100_PartnershipLosses = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line25100", Text "Line_25100_Amount"] Entry Centi Amount, line_25200_NoncapitalLosses :: FieldConst Centi line_25200_NoncapitalLosses = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line25200", Text "Line_25200_Amount"] Entry Centi Amount, line_25300_NetCapitalLosses :: FieldConst Centi line_25300_NetCapitalLosses = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line25300", Text "Line_25300_Amount"] Entry Centi Amount, line_25395_BusinessTransfer :: FieldConst Centi line_25395_BusinessTransfer = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line25395", Text "Line_Amount"] Entry Centi Amount, line_25400_CapitalGainsDeduction :: FieldConst Centi line_25400_CapitalGainsDeduction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line25400", Text "Line_25400_Amount"] Entry Centi Amount, line_25500_NorthernDeductions :: FieldConst Centi line_25500_NorthernDeductions = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line25500", Text "Line_25500_Amount"] Entry Centi Amount, line_25600_AdditionalDeductions_Amount :: FieldConst Centi line_25600_AdditionalDeductions_Amount = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line25600", Text "Line_25600_Amount"] Entry Centi Amount, line_25600_AdditionalDeductions_Specify :: FieldConst Text line_25600_AdditionalDeductions_Specify = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line25600", Text "Line_25600_Specify"] Entry Text Textual, line_25700_sum :: SubCalculation FieldConst line_25700_sum = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "Line25700" [Text "Line_25700_Amount1"] [Text "Line_25700_Amount2"], line72_difference :: FieldConst Centi line72_difference = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line72", Text "Line_26000_Amount"] Entry Centi Amount, line_25999_CapitalGainsReductionAddBack :: FieldConst Centi line_25999_CapitalGainsReductionAddBack = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line25999", Text "Line_Amount"] Entry Centi Amount, line_26000_TaxableIncome :: FieldConst Centi line_26000_TaxableIncome = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line26000", Text "Line_26000_Amount"] Entry Centi Amount} partAFields :: Text -> Int -> Page5PartA FieldConst partAFields :: Text -> Int -> Page5PartA FieldConst partAFields = (Int -> Int -> Bool -> Text) -> Text -> Int -> Page5PartA FieldConst partAFieldsWith Int -> Int -> Bool -> Text forall {a} {a}. (Integral a, Integral a) => a -> a -> Bool -> Text fieldNameAt where fieldNameAt :: a -> a -> Bool -> Text fieldNameAt a line a column Bool isRate = Builder -> Text toText (Builder -> Text) -> Builder -> Text forall a b. (a -> b) -> a -> b $ Builder "Line" Builder -> Builder -> Builder forall a. Semigroup a => a -> a -> a <> a -> Builder forall a. Integral a => a -> Builder decimal a line Builder -> Builder -> Builder forall a. Semigroup a => a -> a -> a <> (if Bool isRate then Builder "Rate" else Builder "Amount") Builder -> Builder -> Builder forall a. Semigroup a => a -> a -> a <> a -> Builder forall a. Integral a => a -> Builder decimal a column toText :: Builder -> Text toText = LazyText -> Text toStrict (LazyText -> Text) -> (Builder -> LazyText) -> Builder -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . Builder -> LazyText toLazyText partAFieldsWith :: (Int -> Int -> Bool -> Text) -> Text -> Int -> Page5PartA FieldConst partAFieldsWith :: (Int -> Int -> Bool -> Text) -> Text -> Int -> Page5PartA FieldConst partAFieldsWith Int -> Int -> Bool -> Text fieldNameAt Text columnPrefix Int startLine = Page5PartA { column1 :: TaxIncomeBracket FieldConst column1 = Int -> Centi -> Rational -> Centi -> TaxIncomeBracket FieldConst column Int 1 Centi 0 Rational 0.15 Centi 0, column2 :: TaxIncomeBracket FieldConst column2 = Int -> Centi -> Rational -> Centi -> TaxIncomeBracket FieldConst column Int 2 Centi 55_867.00 Rational 0.205 Centi 8_380.05, column3 :: TaxIncomeBracket FieldConst column3 = Int -> Centi -> Rational -> Centi -> TaxIncomeBracket FieldConst column Int 3 Centi 111_733.00 Rational 0.26 Centi 19_832.58, column4 :: TaxIncomeBracket FieldConst column4 = Int -> Centi -> Rational -> Centi -> TaxIncomeBracket FieldConst column Int 4 Centi 173_205.00 Rational 0.29 Centi 35_815.30, column5 :: TaxIncomeBracket FieldConst column5 = Int -> Centi -> Rational -> Centi -> TaxIncomeBracket FieldConst column Int 5 Centi 246_752.00 Rational 0.33 Centi 57_143.93} where column :: Int -> Centi -> Rational -> Centi -> TaxIncomeBracket FieldConst column Int n Centi threshold Rational rate Centi baseTax = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within (Text columnPrefix Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Builder -> Text toText (Int -> Builder forall a. Integral a => a -> Builder decimal Int n)) (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.<$> TaxIncomeBracket { income :: FieldConst Centi income = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Int -> Int -> Bool -> Text fieldNameAt Int startLine Int n Bool False] Entry Centi Amount, threshold :: FieldConst Centi threshold = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Int -> Int -> Bool -> Text fieldNameAt (Int startLine Int -> Int -> Int forall a. Num a => a -> a -> a + Int 1) Int n Bool False] (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 [Int -> Int -> Bool -> Text fieldNameAt (Int startLine Int -> Int -> Int forall a. Num a => a -> a -> a + Int 2) Int n Bool False] Entry Centi Amount, rate :: FieldConst Rational rate = [Text] -> Entry Rational -> FieldConst Rational forall a. [Text] -> Entry a -> FieldConst a Field [Int -> Int -> Bool -> Text fieldNameAt (Int startLine Int -> Int -> Int forall a. Num a => a -> a -> a + Int 3) Int n Bool True] (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 [Int -> Int -> Bool -> Text fieldNameAt (Int startLine Int -> Int -> Int forall a. Num a => a -> a -> a + Int 4) Int n Bool False] Entry Centi Amount, baseTax :: FieldConst Centi baseTax = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Int -> Int -> Bool -> Text fieldNameAt (Int startLine Int -> Int -> Int forall a. Num a => a -> a -> a + Int 5) Int n Bool False] (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 [Int -> Int -> Bool -> Text fieldNameAt (Int startLine Int -> Int -> Int forall a. Num a => a -> a -> a + Int 6) Int n Bool False] Entry Centi Amount} toText :: Builder -> Text toText = LazyText -> Text toStrict (LazyText -> Text) -> (Builder -> LazyText) -> Builder -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . Builder -> LazyText toLazyText partBFields :: Page5PartB FieldConst partBFields = Page5PartB { line_30000 :: FieldConst Centi line_30000 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line30000", Text "Line_30000_Amount"] Entry Centi Amount, line_30100 :: FieldConst Centi line_30100 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line30100", Text "Line_30100_Amount"] Entry Centi Amount, line_30300 :: FieldConst Centi line_30300 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line30300", Text "Line_30300_Amount"] Entry Centi Amount, line_30400 :: FieldConst Centi line_30400 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line30400", Text "Line_30400_Amount"] Entry Centi Amount, line_30425 :: FieldConst Centi line_30425 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line30425", Text "Line_30425_Amount"] Entry Centi Amount, line_30450 :: FieldConst Centi line_30450 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line30450", Text "Line_30450_Amount"] Entry Centi Amount, line_30499_ChildrenNum :: FieldConst Word line_30499_ChildrenNum = [Text] -> Entry Word -> FieldConst Word forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line30500", Text "Line30499", Text "Numeric_NoDecimal_BordersAll"] Entry Word Count, line_30500 :: FieldConst Centi line_30500 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line30500", Text "Line_30500_Amount"] Entry Centi Amount, pageBreakSummary :: FieldConst Centi pageBreakSummary = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line89", Text "Amount"] Entry Centi Amount} page6Fields :: Page6 FieldConst page6Fields = Page6 { pageBreakCarry :: FieldConst Centi pageBreakCarry = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line90", Text "Amount"] Entry Centi Amount, line_30800 :: FieldConst Centi line_30800 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line30800", Text "Line_30800_Amount"] Entry Centi Amount, line_31000 :: FieldConst Centi line_31000 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line31000", Text "Line_31000_Amount"] Entry Centi Amount, line_31200 :: FieldConst Centi line_31200 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line31200", Text "Line_31200_Amount"] Entry Centi Amount, line_31205 :: FieldConst Centi line_31205 = FieldConst Centi forall a. FieldConst a NoField, line_31210 :: FieldConst Centi line_31210 = FieldConst Centi forall a. FieldConst a NoField, line_31215 :: FieldConst Centi line_31215 = FieldConst Centi forall a. FieldConst a NoField, line_31217 :: FieldConst Centi line_31217 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line31217", Text "Line_31217_Amount"] Entry Centi Amount, line_31220 :: FieldConst Centi line_31220 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line31220", Text "Line_31220_Amount"] Entry Centi Amount, line_31240 :: FieldConst Centi line_31240 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line31240", Text "Line_31240_Amount"] Entry Centi Amount, line_31260 :: FieldConst Centi line_31260 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line31260", Text "Line_31260_Amount"] Entry Centi Amount, line_31270 :: FieldConst Centi line_31270 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line31270", Text "Line_31270_Amount"] Entry Centi Amount, line_31285 :: FieldConst Centi line_31285 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line31285", Text "Line_31285_Amount"] Entry Centi Amount, line_31300 :: FieldConst Centi line_31300 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line31300", Text "Line_31300_Amount"] Entry Centi Amount, line_31350 :: FieldConst Centi line_31350 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line31350", Text "Line_31350_Amount"] Entry Centi Amount, line102_sum :: SubCalculation FieldConst line102_sum = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "Line102" [Text "Amount1"] [Text "Amount2"], line_31400 :: FieldConst Centi line_31400 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line31400", Text "Line_31400_Amount"] Entry Centi Amount, line104_sum :: FieldConst Centi line104_sum = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line104", Text "Amount"] Entry Centi Amount, line_31600 :: FieldConst Centi line_31600 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line31600", Text "Line_31600_Amount"] Entry Centi Amount, line_31800 :: FieldConst Centi line_31800 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line31800", Text "Line_31800_Amount"] Entry Centi Amount, line107_sum :: FieldConst Centi line107_sum = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line107", Text "Amount"] Entry Centi Amount, line_31900 :: FieldConst Centi line_31900 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line31900", Text "Line_31900_Amount"] Entry Centi Amount, line_32300 :: FieldConst Centi line_32300 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line32300", Text "Line_32300_Amount"] Entry Centi Amount, line_32400 :: FieldConst Centi line_32400 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line32400", Text "Line_32400_Amount"] Entry Centi Amount, line_32600 :: FieldConst Centi line_32600 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line32600", Text "Line_32600_Amount"] Entry Centi Amount, line112_sum :: FieldConst Centi line112_sum = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line112", Text "Amount"] Entry Centi Amount, medical_expenses :: MedicalExpenses FieldConst medical_expenses = MedicalExpenses FieldConst page6MedicalExpensesFields, line_33200_sum :: SubCalculation FieldConst line_33200_sum = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "Line33200" [Text "Line_33200_Amount1"] [Text "Line_33200_Amount2"], line_33500 :: FieldConst Centi line_33500 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line33500", Text "Line_33500_Amount"] Entry Centi Amount, line120_taxCreditRate :: FieldConst Rational line120_taxCreditRate = [Text] -> Entry Rational -> FieldConst Rational forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line120", 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.15 Entry Rational Percent, line_33800 :: FieldConst Centi line_33800 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line33800", Text "Line_33800_Amount"] Entry Centi Amount, line_34900 :: FieldConst Centi line_34900 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line34900", Text "Line_34900_Amount"] Entry Centi Amount, line_35000 :: FieldConst Centi line_35000 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line35000", Text "Line_35000_Amount"] Entry Centi Amount} page6MedicalExpensesFields :: MedicalExpenses FieldConst page6MedicalExpensesFields = MedicalExpenses { familyExpenses :: FieldConst Centi familyExpenses = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line33099", Text "Line_33099_Amount"] Entry Centi Amount, taxableIncome :: FieldConst Centi taxableIncome = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line114", Text "Amount1"] Entry Centi Amount, taxableIncomeFraction :: FieldConst Centi taxableIncomeFraction = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line114", Text "Amount2"] Entry Centi Amount, threshold :: FieldConst Centi threshold = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line115", Text "Amount"] Entry Centi Amount, difference :: FieldConst Centi difference = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line116", Text "Amount"] Entry Centi Amount, otherDependants :: FieldConst Centi otherDependants = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line33199", Text "Line_33199_Amount"] Entry Centi Amount} page7Fields :: Page7 FieldConst page7Fields = Page7 { partC_NetFederalTax :: Page7PartC FieldConst partC_NetFederalTax = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "PartC" (forall {a}. FieldConst a -> FieldConst a) -> Page7PartC FieldConst -> Page7PartC 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) -> Page7PartC p -> Page7PartC q Rank2.<$> Page7PartC FieldConst partCFields, step6_RefundOrBalanceOwing :: Page7Step6 FieldConst step6_RefundOrBalanceOwing = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Step6" (forall {a}. FieldConst a -> FieldConst a) -> Page7Step6 FieldConst -> Page7Step6 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) -> Page7Step6 p -> Page7Step6 q Rank2.<$> Page7Step6 FieldConst page7step6Fields} partCFields :: Page7PartC FieldConst partCFields = Page7PartC { tax_copy :: FieldConst Centi tax_copy = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line124", Text "Amount"] Entry Centi Amount, line_40424 :: FieldConst Centi line_40424 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line40424", Text "Line_40424_Amount"] Entry Centi Amount, line_40400 :: FieldConst Centi line_40400 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line40400", Text "Line_40400_Amount"] Entry Centi Amount, credits_copy :: FieldConst Centi credits_copy = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line127", Text "Amount"] Entry Centi Amount, line_40425 :: FieldConst Centi line_40425 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line40425", Text "Line_40425_Amount"] Entry Centi Amount, line_40427 :: FieldConst Centi line_40427 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line40427", Text "Line_40427_Amount"] Entry Centi Amount, line130_sum :: SubCalculation FieldConst line130_sum = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "Line130" [Text "Amount1"] [Text "Amount2"], line_42900 :: FieldConst Centi line_42900 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line42900", Text "Line_42900_Amount"] Entry Centi Amount, line132_foreignSurtax :: FieldConst Centi line132_foreignSurtax = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line132", Text "Amount"] Entry Centi Amount, line133_sum :: FieldConst Centi line133_sum = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line133", Text "Amount"] Entry Centi Amount, line_40500 :: FieldConst Centi line_40500 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line40500", Text "Line_40500_Amount"] Entry Centi Amount, line135_difference :: FieldConst Centi line135_difference = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line135", Text "Amount"] Entry Centi Amount, line136_recapture :: FieldConst Centi line136_recapture = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line136", Text "Amount"] Entry Centi Amount, line137_sum :: FieldConst Centi line137_sum = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line137", Text "Amount"] Entry Centi Amount, line138_logging :: FieldConst Centi line138_logging = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line138", Text "Amount"] Entry Centi Amount, line_40600 :: FieldConst Centi line_40600 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line40600", Text "Line_40600_Amount"] Entry Centi Amount, line_40900 :: FieldConst Centi line_40900 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line41000", Text "Line40900", Text "Line_40900_Amount"] Entry Centi Amount, line_41000 :: FieldConst Centi line_41000 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line41000", Text "Line_41000_Amount"] Entry Centi Amount, line_41200 :: FieldConst Centi line_41200 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line41200", Text "Line_41200_Amount"] Entry Centi Amount, line_41300 :: FieldConst Centi line_41300 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line41400", Text "Line41300", Text "Line_41300_Amount"] Entry Centi Amount, line_41400 :: FieldConst Centi line_41400 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line41400", Text "Line_41400_Amount"] Entry Centi Amount, line_41600_sum :: SubCalculation FieldConst line_41600_sum = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "Line41600" [Text "Line_41600_Amount1"] [Text "Line_41600_Amount2"], line_41700 :: FieldConst Centi line_41700 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line41700", Text "Line_41700_Amount"] Entry Centi Amount, line_41500 :: FieldConst Centi line_41500 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line41500", Text "Line_41500_Amount"] Entry Centi Amount, line_41800 :: FieldConst Centi line_41800 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line41800", Text "Line_41800_Amount"] Entry Centi Amount, line_42000 :: FieldConst Centi line_42000 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line42000", Text "Line_42000_Amount"] Entry Centi Amount} page7step6Fields :: Page7Step6 FieldConst page7step6Fields = Page7Step6 { tax_copy :: FieldConst Centi tax_copy = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line148", Text "Amount"] Entry Centi Amount, line_42100_CPPContributions :: FieldConst Centi line_42100_CPPContributions = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line42100", Text "Line_42100_Amount"] Entry Centi Amount, line_42120_EIPremiums :: FieldConst Centi line_42120_EIPremiums = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line42120", Text "Line_42120_Amount"] Entry Centi Amount, line_42200_SocialBenefits :: FieldConst Centi line_42200_SocialBenefits = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line42200", Text "Line_42200_Amount"] Entry Centi Amount, line_42800_ProvTerrTax :: FieldConst Centi line_42800_ProvTerrTax = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line42800", Text "Line_42800_Amount"] Entry Centi Amount, line_43200_FirstNationsTax :: FieldConst Centi line_43200_FirstNationsTax = FieldConst Centi forall a. FieldConst a NoField, line_43500_TotalPayable :: FieldConst Centi line_43500_TotalPayable = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line43500", Text "Line_43500_Amount"] Entry Centi Amount} page8Fields :: Page8 FieldConst page8Fields = Page8 { step6_RefundOrBalanceOwing :: Page8Step6 FieldConst step6_RefundOrBalanceOwing = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Step6-Continued" (forall {a}. FieldConst a -> FieldConst a) -> Page8Step6 FieldConst -> Page8Step6 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) -> Page8Step6 p -> Page8Step6 q Rank2.<$> Page8Step6 FieldConst page8step6Fields, line_48400_Refund :: FieldConst Centi line_48400_Refund = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Refund_or_Balance-owing", Text "Line48400", Text "Line_48400_Amount"] Entry Centi Amount, line_48500_BalanceOwing :: FieldConst Centi line_48500_BalanceOwing = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Refund_or_Balance-owing", Text "Line48500", Text "Line_48500_Amount"] Entry Centi Amount, telephone :: FieldConst Centi telephone = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Certification", Text "Telephone"] Entry Centi Amount, date :: FieldConst Centi date = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Certification", Text "Date"] Entry Centi Amount, taxPreparer :: TaxPreparer FieldConst taxPreparer = Text -> FieldConst a -> FieldConst a forall x. Text -> FieldConst x -> FieldConst x within Text "Line_49000_IfFeeWasCharged" (forall {a}. FieldConst a -> FieldConst a) -> TaxPreparer FieldConst -> TaxPreparer 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) -> TaxPreparer p -> TaxPreparer q Rank2.<$> TaxPreparer FieldConst taxPreparerFields, line1_ONOpportunitiesFund :: FieldConst Centi line1_ONOpportunitiesFund = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "ONOpportunitiesFund2", Text "Line_1", Text "Amount"] Entry Centi Amount, line_46500 :: FieldConst Centi line_46500 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "ONOpportunitiesFund2", Text "Line_2", Text "Amount"] Entry Centi Amount, line_46600 :: FieldConst Centi line_46600 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "ONOpportunitiesFund2", Text "Line_3", Text "Amount"] Entry Centi Amount} page8step6Fields :: Page8Step6 FieldConst page8step6Fields = Page8Step6 { line_43500_totalpayable :: FieldConst Centi line_43500_totalpayable = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line154", Text "Amount"] Entry Centi Amount, line_43700_Total_income_tax_ded :: FieldConst Centi line_43700_Total_income_tax_ded = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line43700", Text "Line_43700_Amount"] Entry Centi Amount, line_43800_TaxTransferQC :: FieldConst Centi line_43800_TaxTransferQC = FieldConst Centi forall a. FieldConst a NoField, line_43850_diff :: SubCalculation FieldConst line_43850_diff = (forall a. FieldConst a) -> SubCalculation FieldConst forall {k} (g :: (k -> *) -> *) (f :: k -> *). Applicative g => (forall (a :: k). f a) -> g f forall (f :: * -> *). (forall a. f a) -> SubCalculation f Rank2.pure FieldConst a forall a. FieldConst a NoField, line_42900_copy :: FieldConst Centi line_42900_copy = FieldConst Centi forall a. FieldConst a NoField, line_44000 :: FieldConst Centi line_44000 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line44000", Text "Line_44000_Amount"] Entry Centi Amount, line_44100 :: FieldConst Centi line_44100 = FieldConst Centi forall a. FieldConst a NoField, line_44800_CPPOverpayment :: FieldConst Centi line_44800_CPPOverpayment = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line44800", Text "Line_44800_Amount"] Entry Centi Amount, line_45000_EIOverpayment :: FieldConst Centi line_45000_EIOverpayment = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line45000", Text "Line_45000_Amount"] Entry Centi Amount, line_31210_copy :: FieldConst Centi line_31210_copy = FieldConst Centi forall a. FieldConst a NoField, line_45100_diff :: SubCalculation FieldConst line_45100_diff = (forall a. FieldConst a) -> SubCalculation FieldConst forall {k} (g :: (k -> *) -> *) (f :: k -> *). Applicative g => (forall (a :: k). f a) -> g f forall (f :: * -> *). (forall a. f a) -> SubCalculation f Rank2.pure FieldConst a forall a. FieldConst a NoField, line_45200_MedicalExpense :: FieldConst Centi line_45200_MedicalExpense = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line45200", Text "Line_45200_Amount"] Entry Centi Amount, line_45300_CWB :: FieldConst Centi line_45300_CWB = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line45300", Text "Line_45300_Amount"] Entry Centi Amount, line_45350_CTC :: FieldConst Centi line_45350_CTC = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line45350", Text "Line_45350_Amount"] Entry Centi Amount, line_45355_MHRTC :: FieldConst Centi line_45355_MHRTC = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line45355", Text "Line_45355_Amount"] Entry Centi Amount, line_45400_InvestmentTaxCredit :: FieldConst Centi line_45400_InvestmentTaxCredit = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line45400", Text "Line_45400_Amount"] Entry Centi Amount, line_45600_TrustTaxCredit :: FieldConst Centi line_45600_TrustTaxCredit = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line45600", Text "Line_45600_Amount"] Entry Centi Amount, line_45700_GST_HST_Rebate :: FieldConst Centi line_45700_GST_HST_Rebate = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line45700", Text "Line_45700_Amount"] Entry Centi Amount, line_46800 :: FieldConst Centi line_46800 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line46900", Text "Line46800", Text "Line_46800_Amount"] Entry Centi Amount, line_46900 :: FieldConst Centi line_46900 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line46900", Text "Line_46900_Amount"] Entry Centi Amount, line_47555_TaxPaid :: FieldConst Centi line_47555_TaxPaid = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line47555", Text "Line_47600_Amount"] Entry Centi Amount, line_47556 :: FieldConst Centi line_47556 = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line47556", Text "Line_47556_Amount"] Entry Centi Amount, line_47557 :: FieldConst Centi line_47557 = FieldConst Centi forall a. FieldConst a NoField, line_47600_TaxPaid :: FieldConst Centi line_47600_TaxPaid = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line47600", Text "Line_47600_Amount"] Entry Centi Amount, line_47900_ProvTerrCredits :: FieldConst Centi line_47900_ProvTerrCredits = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line47900", Text "Line_47900_Amount"] Entry Centi Amount, line_48200_sum :: SubCalculation FieldConst line_48200_sum = Text -> [Text] -> [Text] -> SubCalculation FieldConst subCalculationFields Text "Line48200" [Text "Line_48200_Amount1"] [Text "Line_48200_Amount2"], line164_Refund_or_BalanceOwing :: FieldConst Centi line164_Refund_or_BalanceOwing = [Text] -> Entry Centi -> FieldConst Centi forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line172", Text "Amount"] Entry Centi Amount} taxPreparerFields :: TaxPreparer FieldConst taxPreparerFields = TaxPreparer { eFileNumber :: FieldConst Text eFileNumber = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "EFileNumber_Comb", Text "EFile"] Entry Text Textual, nameOfPreparer :: FieldConst Text nameOfPreparer = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "NameOfPreparer"] Entry Text Textual, telephoneOfPreparer :: FieldConst Text telephoneOfPreparer = [Text] -> Entry Text -> FieldConst Text forall a. [Text] -> Entry a -> FieldConst a Field [Text "TelephoneOfPreparer"] Entry Text Textual, line_49000_WasAFeeCharged :: FieldConst Bool line_49000_WasAFeeCharged = [Text] -> Entry Bool -> FieldConst Bool forall a. [Text] -> Entry a -> FieldConst a Field [Text "Line49000_CheckBoxGroup"] (Entry Bool -> FieldConst Bool) -> Entry Bool -> FieldConst Bool forall a b. (a -> b) -> a -> b $ Text -> Entry Bool Switch' Text "Line49000_CheckBox_EN"}