canadian-income-tax-2022.2.1: Canadian income tax calculation
Safe HaskellSafe-Inferred
LanguageHaskell2010

Tax.Canada.T1.Types

Documentation

data T1 line Source #

Constructors

T1 

Fields

Instances

Instances details
Applicative T1 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> T1 f #

Apply T1 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). T1 (p ~> q) -> T1 p -> T1 q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> T1 p -> T1 q -> T1 r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> T1 p -> T1 q -> T1 r -> T1 s #

Distributive T1 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> T1 q) -> p a -> T1 (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (T1 q) -> T1 (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (T1 p) -> T1 q #

DistributiveTraversable T1 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> T1 f2) -> f1 a -> T1 (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (T1 f2) -> T1 (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (T1 f2) -> T1 f #

Foldable T1 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> T1 p -> m #

Functor T1 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> T1 p -> T1 q #

Logistic T1 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (T1 q -> T1 q) -> T1 (Compose p (q ~> q)) #

Traversable T1 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> T1 p -> m (T1 q) #

sequence :: forall m (p :: k -> Type). Applicative m => T1 (Compose m p) -> m (T1 p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (T1 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

showsPrec :: Int -> T1 line -> ShowS #

show :: T1 line -> String #

showList :: [T1 line] -> ShowS #

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (T1 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: T1 line -> T1 line -> Bool #

(/=) :: T1 line -> T1 line -> Bool #

data Page1 line Source #

Constructors

Page1 

Fields

Instances

Instances details
Applicative Page1 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> Page1 f #

Apply Page1 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Page1 (p ~> q) -> Page1 p -> Page1 q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Page1 p -> Page1 q -> Page1 r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Page1 p -> Page1 q -> Page1 r -> Page1 s #

Distributive Page1 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> Page1 q) -> p a -> Page1 (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (Page1 q) -> Page1 (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (Page1 p) -> Page1 q #

DistributiveTraversable Page1 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Page1 f2) -> f1 a -> Page1 (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Page1 f2) -> Page1 (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (Page1 f2) -> Page1 f #

Foldable Page1 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Page1 p -> m #

Functor Page1 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Page1 p -> Page1 q #

Logistic Page1 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (Page1 q -> Page1 q) -> Page1 (Compose p (q ~> q)) #

Traversable Page1 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Page1 p -> m (Page1 q) #

sequence :: forall m (p :: k -> Type). Applicative m => Page1 (Compose m p) -> m (Page1 p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (Page1 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

showsPrec :: Int -> Page1 line -> ShowS #

show :: Page1 line -> String #

showList :: [Page1 line] -> ShowS #

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (Page1 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: Page1 line -> Page1 line -> Bool #

(/=) :: Page1 line -> Page1 line -> Bool #

data Identification line Source #

Constructors

Identification 

Fields

Instances

Instances details
Applicative Identification Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> Identification f #

Apply Identification Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Identification (p ~> q) -> Identification p -> Identification q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Identification p -> Identification q -> Identification r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Identification p -> Identification q -> Identification r -> Identification s #

Distributive Identification Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> Identification q) -> p a -> Identification (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (Identification q) -> Identification (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (Identification p) -> Identification q #

DistributiveTraversable Identification Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Identification f2) -> f1 a -> Identification (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Identification f2) -> Identification (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (Identification f2) -> Identification f #

Foldable Identification Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Identification p -> m #

Functor Identification Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Identification p -> Identification q #

Logistic Identification Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (Identification q -> Identification q) -> Identification (Compose p (q ~> q)) #

Traversable Identification Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Identification p -> m (Identification q) #

sequence :: forall m (p :: k -> Type). Applicative m => Identification (Compose m p) -> m (Identification p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (Identification line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (Identification line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: Identification line -> Identification line -> Bool #

(/=) :: Identification line -> Identification line -> Bool #

data Residence line Source #

Constructors

Residence 

Instances

Instances details
Applicative Residence Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> Residence f #

Apply Residence Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Residence (p ~> q) -> Residence p -> Residence q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Residence p -> Residence q -> Residence r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Residence p -> Residence q -> Residence r -> Residence s #

Distributive Residence Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> Residence q) -> p a -> Residence (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (Residence q) -> Residence (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (Residence p) -> Residence q #

DistributiveTraversable Residence Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Residence f2) -> f1 a -> Residence (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Residence f2) -> Residence (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (Residence f2) -> Residence f #

Foldable Residence Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Residence p -> m #

Functor Residence Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Residence p -> Residence q #

Logistic Residence Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (Residence q -> Residence q) -> Residence (Compose p (q ~> q)) #

Traversable Residence Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Residence p -> m (Residence q) #

sequence :: forall m (p :: k -> Type). Applicative m => Residence (Compose m p) -> m (Residence p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (Residence line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

showsPrec :: Int -> Residence line -> ShowS #

show :: Residence line -> String #

showList :: [Residence line] -> ShowS #

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (Residence line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: Residence line -> Residence line -> Bool #

(/=) :: Residence line -> Residence line -> Bool #

data Spouse line Source #

Constructors

Spouse 

Fields

Instances

Instances details
Applicative Spouse Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> Spouse f #

Apply Spouse Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Spouse (p ~> q) -> Spouse p -> Spouse q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Spouse p -> Spouse q -> Spouse r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Spouse p -> Spouse q -> Spouse r -> Spouse s #

Distributive Spouse Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> Spouse q) -> p a -> Spouse (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (Spouse q) -> Spouse (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (Spouse p) -> Spouse q #

DistributiveTraversable Spouse Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Spouse f2) -> f1 a -> Spouse (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Spouse f2) -> Spouse (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (Spouse f2) -> Spouse f #

Foldable Spouse Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Spouse p -> m #

Functor Spouse Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Spouse p -> Spouse q #

Logistic Spouse Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (Spouse q -> Spouse q) -> Spouse (Compose p (q ~> q)) #

Traversable Spouse Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Spouse p -> m (Spouse q) #

sequence :: forall m (p :: k -> Type). Applicative m => Spouse (Compose m p) -> m (Spouse p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (Spouse line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

showsPrec :: Int -> Spouse line -> ShowS #

show :: Spouse line -> String #

showList :: [Spouse line] -> ShowS #

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (Spouse line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: Spouse line -> Spouse line -> Bool #

(/=) :: Spouse line -> Spouse line -> Bool #

data Page2 line Source #

Constructors

Page2 

Fields

Instances

Instances details
Applicative Page2 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> Page2 f #

Apply Page2 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Page2 (p ~> q) -> Page2 p -> Page2 q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Page2 p -> Page2 q -> Page2 r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Page2 p -> Page2 q -> Page2 r -> Page2 s #

Distributive Page2 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> Page2 q) -> p a -> Page2 (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (Page2 q) -> Page2 (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (Page2 p) -> Page2 q #

DistributiveTraversable Page2 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Page2 f2) -> f1 a -> Page2 (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Page2 f2) -> Page2 (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (Page2 f2) -> Page2 f #

Foldable Page2 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Page2 p -> m #

Functor Page2 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Page2 p -> Page2 q #

Logistic Page2 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (Page2 q -> Page2 q) -> Page2 (Compose p (q ~> q)) #

Traversable Page2 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Page2 p -> m (Page2 q) #

sequence :: forall m (p :: k -> Type). Applicative m => Page2 (Compose m p) -> m (Page2 p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (Page2 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

showsPrec :: Int -> Page2 line -> ShowS #

show :: Page2 line -> String #

showList :: [Page2 line] -> ShowS #

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (Page2 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: Page2 line -> Page2 line -> Bool #

(/=) :: Page2 line -> Page2 line -> Bool #

data ElectionsCanada line Source #

Constructors

ElectionsCanada 

Fields

Instances

Instances details
Applicative ElectionsCanada Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> ElectionsCanada f #

Apply ElectionsCanada Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). ElectionsCanada (p ~> q) -> ElectionsCanada p -> ElectionsCanada q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> ElectionsCanada p -> ElectionsCanada q -> ElectionsCanada r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> ElectionsCanada p -> ElectionsCanada q -> ElectionsCanada r -> ElectionsCanada s #

Distributive ElectionsCanada Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> ElectionsCanada q) -> p a -> ElectionsCanada (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (ElectionsCanada q) -> ElectionsCanada (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (ElectionsCanada p) -> ElectionsCanada q #

DistributiveTraversable ElectionsCanada Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> ElectionsCanada f2) -> f1 a -> ElectionsCanada (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (ElectionsCanada f2) -> ElectionsCanada (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (ElectionsCanada f2) -> ElectionsCanada f #

Foldable ElectionsCanada Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> ElectionsCanada p -> m #

Functor ElectionsCanada Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> ElectionsCanada p -> ElectionsCanada q #

Logistic ElectionsCanada Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (ElectionsCanada q -> ElectionsCanada q) -> ElectionsCanada (Compose p (q ~> q)) #

Traversable ElectionsCanada Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> ElectionsCanada p -> m (ElectionsCanada q) #

sequence :: forall m (p :: k -> Type). Applicative m => ElectionsCanada (Compose m p) -> m (ElectionsCanada p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (ElectionsCanada line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (ElectionsCanada line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: ElectionsCanada line -> ElectionsCanada line -> Bool #

(/=) :: ElectionsCanada line -> ElectionsCanada line -> Bool #

data Page3 line Source #

Constructors

Page3 

Fields

Instances

Instances details
Applicative Page3 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> Page3 f #

Apply Page3 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Page3 (p ~> q) -> Page3 p -> Page3 q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Page3 p -> Page3 q -> Page3 r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Page3 p -> Page3 q -> Page3 r -> Page3 s #

Distributive Page3 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> Page3 q) -> p a -> Page3 (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (Page3 q) -> Page3 (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (Page3 p) -> Page3 q #

DistributiveTraversable Page3 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Page3 f2) -> f1 a -> Page3 (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Page3 f2) -> Page3 (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (Page3 f2) -> Page3 f #

Foldable Page3 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Page3 p -> m #

Functor Page3 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Page3 p -> Page3 q #

Logistic Page3 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (Page3 q -> Page3 q) -> Page3 (Compose p (q ~> q)) #

Traversable Page3 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Page3 p -> m (Page3 q) #

sequence :: forall m (p :: k -> Type). Applicative m => Page3 (Compose m p) -> m (Page3 p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (Page3 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

showsPrec :: Int -> Page3 line -> ShowS #

show :: Page3 line -> String #

showList :: [Page3 line] -> ShowS #

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (Page3 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: Page3 line -> Page3 line -> Bool #

(/=) :: Page3 line -> Page3 line -> Bool #

data Page4 line Source #

Instances

Instances details
Applicative Page4 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> Page4 f #

Apply Page4 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Page4 (p ~> q) -> Page4 p -> Page4 q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Page4 p -> Page4 q -> Page4 r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Page4 p -> Page4 q -> Page4 r -> Page4 s #

Distributive Page4 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> Page4 q) -> p a -> Page4 (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (Page4 q) -> Page4 (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (Page4 p) -> Page4 q #

DistributiveTraversable Page4 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Page4 f2) -> f1 a -> Page4 (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Page4 f2) -> Page4 (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (Page4 f2) -> Page4 f #

Foldable Page4 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Page4 p -> m #

Functor Page4 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Page4 p -> Page4 q #

Logistic Page4 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (Page4 q -> Page4 q) -> Page4 (Compose p (q ~> q)) #

Traversable Page4 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Page4 p -> m (Page4 q) #

sequence :: forall m (p :: k -> Type). Applicative m => Page4 (Compose m p) -> m (Page4 p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (Page4 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

showsPrec :: Int -> Page4 line -> ShowS #

show :: Page4 line -> String #

showList :: [Page4 line] -> ShowS #

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (Page4 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: Page4 line -> Page4 line -> Bool #

(/=) :: Page4 line -> Page4 line -> Bool #

data Page5 line Source #

Instances

Instances details
Applicative Page5 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> Page5 f #

Apply Page5 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Page5 (p ~> q) -> Page5 p -> Page5 q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Page5 p -> Page5 q -> Page5 r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Page5 p -> Page5 q -> Page5 r -> Page5 s #

Distributive Page5 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> Page5 q) -> p a -> Page5 (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (Page5 q) -> Page5 (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (Page5 p) -> Page5 q #

DistributiveTraversable Page5 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Page5 f2) -> f1 a -> Page5 (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Page5 f2) -> Page5 (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (Page5 f2) -> Page5 f #

Foldable Page5 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Page5 p -> m #

Functor Page5 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Page5 p -> Page5 q #

Logistic Page5 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (Page5 q -> Page5 q) -> Page5 (Compose p (q ~> q)) #

Traversable Page5 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Page5 p -> m (Page5 q) #

sequence :: forall m (p :: k -> Type). Applicative m => Page5 (Compose m p) -> m (Page5 p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (Page5 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

showsPrec :: Int -> Page5 line -> ShowS #

show :: Page5 line -> String #

showList :: [Page5 line] -> ShowS #

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (Page5 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: Page5 line -> Page5 line -> Bool #

(/=) :: Page5 line -> Page5 line -> Bool #

data Step4 line Source #

Instances

Instances details
Applicative Step4 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> Step4 f #

Apply Step4 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Step4 (p ~> q) -> Step4 p -> Step4 q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Step4 p -> Step4 q -> Step4 r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Step4 p -> Step4 q -> Step4 r -> Step4 s #

Distributive Step4 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> Step4 q) -> p a -> Step4 (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (Step4 q) -> Step4 (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (Step4 p) -> Step4 q #

DistributiveTraversable Step4 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Step4 f2) -> f1 a -> Step4 (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Step4 f2) -> Step4 (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (Step4 f2) -> Step4 f #

Foldable Step4 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Step4 p -> m #

Functor Step4 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Step4 p -> Step4 q #

Logistic Step4 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (Step4 q -> Step4 q) -> Step4 (Compose p (q ~> q)) #

Traversable Step4 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Step4 p -> m (Step4 q) #

sequence :: forall m (p :: k -> Type). Applicative m => Step4 (Compose m p) -> m (Step4 p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (Step4 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

showsPrec :: Int -> Step4 line -> ShowS #

show :: Step4 line -> String #

showList :: [Step4 line] -> ShowS #

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (Step4 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: Step4 line -> Step4 line -> Bool #

(/=) :: Step4 line -> Step4 line -> Bool #

data Page5PartA line Source #

Instances

Instances details
Applicative Page5PartA Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> Page5PartA f #

Apply Page5PartA Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Page5PartA (p ~> q) -> Page5PartA p -> Page5PartA q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Page5PartA p -> Page5PartA q -> Page5PartA r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Page5PartA p -> Page5PartA q -> Page5PartA r -> Page5PartA s #

Distributive Page5PartA Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> Page5PartA q) -> p a -> Page5PartA (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (Page5PartA q) -> Page5PartA (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (Page5PartA p) -> Page5PartA q #

DistributiveTraversable Page5PartA Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Page5PartA f2) -> f1 a -> Page5PartA (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Page5PartA f2) -> Page5PartA (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (Page5PartA f2) -> Page5PartA f #

Foldable Page5PartA Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Page5PartA p -> m #

Functor Page5PartA Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Page5PartA p -> Page5PartA q #

Logistic Page5PartA Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (Page5PartA q -> Page5PartA q) -> Page5PartA (Compose p (q ~> q)) #

Traversable Page5PartA Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Page5PartA p -> m (Page5PartA q) #

sequence :: forall m (p :: k -> Type). Applicative m => Page5PartA (Compose m p) -> m (Page5PartA p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (Page5PartA line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

showsPrec :: Int -> Page5PartA line -> ShowS #

show :: Page5PartA line -> String #

showList :: [Page5PartA line] -> ShowS #

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (Page5PartA line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: Page5PartA line -> Page5PartA line -> Bool #

(/=) :: Page5PartA line -> Page5PartA line -> Bool #

data Page5PartB line Source #

Constructors

Page5PartB 

Fields

Instances

Instances details
Applicative Page5PartB Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> Page5PartB f #

Apply Page5PartB Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Page5PartB (p ~> q) -> Page5PartB p -> Page5PartB q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Page5PartB p -> Page5PartB q -> Page5PartB r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Page5PartB p -> Page5PartB q -> Page5PartB r -> Page5PartB s #

Distributive Page5PartB Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> Page5PartB q) -> p a -> Page5PartB (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (Page5PartB q) -> Page5PartB (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (Page5PartB p) -> Page5PartB q #

DistributiveTraversable Page5PartB Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Page5PartB f2) -> f1 a -> Page5PartB (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Page5PartB f2) -> Page5PartB (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (Page5PartB f2) -> Page5PartB f #

Foldable Page5PartB Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Page5PartB p -> m #

Functor Page5PartB Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Page5PartB p -> Page5PartB q #

Logistic Page5PartB Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (Page5PartB q -> Page5PartB q) -> Page5PartB (Compose p (q ~> q)) #

Traversable Page5PartB Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Page5PartB p -> m (Page5PartB q) #

sequence :: forall m (p :: k -> Type). Applicative m => Page5PartB (Compose m p) -> m (Page5PartB p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (Page5PartB line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

showsPrec :: Int -> Page5PartB line -> ShowS #

show :: Page5PartB line -> String #

showList :: [Page5PartB line] -> ShowS #

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (Page5PartB line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: Page5PartB line -> Page5PartB line -> Bool #

(/=) :: Page5PartB line -> Page5PartB line -> Bool #

data TaxIncomeBracket line Source #

Instances

Instances details
Applicative TaxIncomeBracket Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> TaxIncomeBracket f #

Apply TaxIncomeBracket Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). TaxIncomeBracket (p ~> q) -> TaxIncomeBracket p -> TaxIncomeBracket q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> TaxIncomeBracket p -> TaxIncomeBracket q -> TaxIncomeBracket r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> TaxIncomeBracket p -> TaxIncomeBracket q -> TaxIncomeBracket r -> TaxIncomeBracket s #

Distributive TaxIncomeBracket Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> TaxIncomeBracket q) -> p a -> TaxIncomeBracket (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (TaxIncomeBracket q) -> TaxIncomeBracket (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (TaxIncomeBracket p) -> TaxIncomeBracket q #

DistributiveTraversable TaxIncomeBracket Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> TaxIncomeBracket f2) -> f1 a -> TaxIncomeBracket (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (TaxIncomeBracket f2) -> TaxIncomeBracket (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (TaxIncomeBracket f2) -> TaxIncomeBracket f #

Foldable TaxIncomeBracket Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> TaxIncomeBracket p -> m #

Functor TaxIncomeBracket Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> TaxIncomeBracket p -> TaxIncomeBracket q #

Logistic TaxIncomeBracket Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (TaxIncomeBracket q -> TaxIncomeBracket q) -> TaxIncomeBracket (Compose p (q ~> q)) #

Traversable TaxIncomeBracket Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> TaxIncomeBracket p -> m (TaxIncomeBracket q) #

sequence :: forall m (p :: k -> Type). Applicative m => TaxIncomeBracket (Compose m p) -> m (TaxIncomeBracket p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (TaxIncomeBracket line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (TaxIncomeBracket line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

data Page6 line Source #

Constructors

Page6 

Fields

Instances

Instances details
Applicative Page6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> Page6 f #

Apply Page6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Page6 (p ~> q) -> Page6 p -> Page6 q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Page6 p -> Page6 q -> Page6 r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Page6 p -> Page6 q -> Page6 r -> Page6 s #

Distributive Page6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> Page6 q) -> p a -> Page6 (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (Page6 q) -> Page6 (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (Page6 p) -> Page6 q #

DistributiveTraversable Page6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Page6 f2) -> f1 a -> Page6 (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Page6 f2) -> Page6 (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (Page6 f2) -> Page6 f #

Foldable Page6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Page6 p -> m #

Functor Page6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Page6 p -> Page6 q #

Logistic Page6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (Page6 q -> Page6 q) -> Page6 (Compose p (q ~> q)) #

Traversable Page6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Page6 p -> m (Page6 q) #

sequence :: forall m (p :: k -> Type). Applicative m => Page6 (Compose m p) -> m (Page6 p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (Page6 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

showsPrec :: Int -> Page6 line -> ShowS #

show :: Page6 line -> String #

showList :: [Page6 line] -> ShowS #

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (Page6 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: Page6 line -> Page6 line -> Bool #

(/=) :: Page6 line -> Page6 line -> Bool #

data MedicalExpenses line Source #

Constructors

MedicalExpenses 

Instances

Instances details
Applicative MedicalExpenses Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> MedicalExpenses f #

Apply MedicalExpenses Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). MedicalExpenses (p ~> q) -> MedicalExpenses p -> MedicalExpenses q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> MedicalExpenses p -> MedicalExpenses q -> MedicalExpenses r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> MedicalExpenses p -> MedicalExpenses q -> MedicalExpenses r -> MedicalExpenses s #

Distributive MedicalExpenses Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> MedicalExpenses q) -> p a -> MedicalExpenses (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (MedicalExpenses q) -> MedicalExpenses (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (MedicalExpenses p) -> MedicalExpenses q #

DistributiveTraversable MedicalExpenses Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> MedicalExpenses f2) -> f1 a -> MedicalExpenses (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (MedicalExpenses f2) -> MedicalExpenses (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (MedicalExpenses f2) -> MedicalExpenses f #

Foldable MedicalExpenses Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> MedicalExpenses p -> m #

Functor MedicalExpenses Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> MedicalExpenses p -> MedicalExpenses q #

Logistic MedicalExpenses Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (MedicalExpenses q -> MedicalExpenses q) -> MedicalExpenses (Compose p (q ~> q)) #

Traversable MedicalExpenses Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> MedicalExpenses p -> m (MedicalExpenses q) #

sequence :: forall m (p :: k -> Type). Applicative m => MedicalExpenses (Compose m p) -> m (MedicalExpenses p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (MedicalExpenses line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (MedicalExpenses line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: MedicalExpenses line -> MedicalExpenses line -> Bool #

(/=) :: MedicalExpenses line -> MedicalExpenses line -> Bool #

data Page7 line Source #

Instances

Instances details
Applicative Page7 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> Page7 f #

Apply Page7 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Page7 (p ~> q) -> Page7 p -> Page7 q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Page7 p -> Page7 q -> Page7 r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Page7 p -> Page7 q -> Page7 r -> Page7 s #

Distributive Page7 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> Page7 q) -> p a -> Page7 (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (Page7 q) -> Page7 (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (Page7 p) -> Page7 q #

DistributiveTraversable Page7 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Page7 f2) -> f1 a -> Page7 (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Page7 f2) -> Page7 (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (Page7 f2) -> Page7 f #

Foldable Page7 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Page7 p -> m #

Functor Page7 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Page7 p -> Page7 q #

Logistic Page7 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (Page7 q -> Page7 q) -> Page7 (Compose p (q ~> q)) #

Traversable Page7 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Page7 p -> m (Page7 q) #

sequence :: forall m (p :: k -> Type). Applicative m => Page7 (Compose m p) -> m (Page7 p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (Page7 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

showsPrec :: Int -> Page7 line -> ShowS #

show :: Page7 line -> String #

showList :: [Page7 line] -> ShowS #

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (Page7 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: Page7 line -> Page7 line -> Bool #

(/=) :: Page7 line -> Page7 line -> Bool #

data Page7PartC line Source #

Constructors

Page7PartC 

Fields

Instances

Instances details
Applicative Page7PartC Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> Page7PartC f #

Apply Page7PartC Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Page7PartC (p ~> q) -> Page7PartC p -> Page7PartC q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Page7PartC p -> Page7PartC q -> Page7PartC r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Page7PartC p -> Page7PartC q -> Page7PartC r -> Page7PartC s #

Distributive Page7PartC Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> Page7PartC q) -> p a -> Page7PartC (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (Page7PartC q) -> Page7PartC (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (Page7PartC p) -> Page7PartC q #

DistributiveTraversable Page7PartC Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Page7PartC f2) -> f1 a -> Page7PartC (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Page7PartC f2) -> Page7PartC (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (Page7PartC f2) -> Page7PartC f #

Foldable Page7PartC Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Page7PartC p -> m #

Functor Page7PartC Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Page7PartC p -> Page7PartC q #

Logistic Page7PartC Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (Page7PartC q -> Page7PartC q) -> Page7PartC (Compose p (q ~> q)) #

Traversable Page7PartC Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Page7PartC p -> m (Page7PartC q) #

sequence :: forall m (p :: k -> Type). Applicative m => Page7PartC (Compose m p) -> m (Page7PartC p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (Page7PartC line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

showsPrec :: Int -> Page7PartC line -> ShowS #

show :: Page7PartC line -> String #

showList :: [Page7PartC line] -> ShowS #

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (Page7PartC line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: Page7PartC line -> Page7PartC line -> Bool #

(/=) :: Page7PartC line -> Page7PartC line -> Bool #

data Page7Step6 line Source #

Instances

Instances details
Applicative Page7Step6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> Page7Step6 f #

Apply Page7Step6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Page7Step6 (p ~> q) -> Page7Step6 p -> Page7Step6 q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Page7Step6 p -> Page7Step6 q -> Page7Step6 r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Page7Step6 p -> Page7Step6 q -> Page7Step6 r -> Page7Step6 s #

Distributive Page7Step6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> Page7Step6 q) -> p a -> Page7Step6 (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (Page7Step6 q) -> Page7Step6 (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (Page7Step6 p) -> Page7Step6 q #

DistributiveTraversable Page7Step6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Page7Step6 f2) -> f1 a -> Page7Step6 (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Page7Step6 f2) -> Page7Step6 (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (Page7Step6 f2) -> Page7Step6 f #

Foldable Page7Step6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Page7Step6 p -> m #

Functor Page7Step6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Page7Step6 p -> Page7Step6 q #

Logistic Page7Step6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (Page7Step6 q -> Page7Step6 q) -> Page7Step6 (Compose p (q ~> q)) #

Traversable Page7Step6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Page7Step6 p -> m (Page7Step6 q) #

sequence :: forall m (p :: k -> Type). Applicative m => Page7Step6 (Compose m p) -> m (Page7Step6 p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (Page7Step6 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

showsPrec :: Int -> Page7Step6 line -> ShowS #

show :: Page7Step6 line -> String #

showList :: [Page7Step6 line] -> ShowS #

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (Page7Step6 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: Page7Step6 line -> Page7Step6 line -> Bool #

(/=) :: Page7Step6 line -> Page7Step6 line -> Bool #

data Page8 line Source #

Instances

Instances details
Applicative Page8 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> Page8 f #

Apply Page8 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Page8 (p ~> q) -> Page8 p -> Page8 q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Page8 p -> Page8 q -> Page8 r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Page8 p -> Page8 q -> Page8 r -> Page8 s #

Distributive Page8 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> Page8 q) -> p a -> Page8 (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (Page8 q) -> Page8 (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (Page8 p) -> Page8 q #

DistributiveTraversable Page8 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Page8 f2) -> f1 a -> Page8 (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Page8 f2) -> Page8 (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (Page8 f2) -> Page8 f #

Foldable Page8 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Page8 p -> m #

Functor Page8 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Page8 p -> Page8 q #

Logistic Page8 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (Page8 q -> Page8 q) -> Page8 (Compose p (q ~> q)) #

Traversable Page8 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Page8 p -> m (Page8 q) #

sequence :: forall m (p :: k -> Type). Applicative m => Page8 (Compose m p) -> m (Page8 p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (Page8 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

showsPrec :: Int -> Page8 line -> ShowS #

show :: Page8 line -> String #

showList :: [Page8 line] -> ShowS #

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (Page8 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: Page8 line -> Page8 line -> Bool #

(/=) :: Page8 line -> Page8 line -> Bool #

data Page8Step6 line Source #

Instances

Instances details
Applicative Page8Step6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> Page8Step6 f #

Apply Page8Step6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). Page8Step6 (p ~> q) -> Page8Step6 p -> Page8Step6 q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> Page8Step6 p -> Page8Step6 q -> Page8Step6 r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> Page8Step6 p -> Page8Step6 q -> Page8Step6 r -> Page8Step6 s #

Distributive Page8Step6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> Page8Step6 q) -> p a -> Page8Step6 (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (Page8Step6 q) -> Page8Step6 (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (Page8Step6 p) -> Page8Step6 q #

DistributiveTraversable Page8Step6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> Page8Step6 f2) -> f1 a -> Page8Step6 (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (Page8Step6 f2) -> Page8Step6 (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (Page8Step6 f2) -> Page8Step6 f #

Foldable Page8Step6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> Page8Step6 p -> m #

Functor Page8Step6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> Page8Step6 p -> Page8Step6 q #

Logistic Page8Step6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (Page8Step6 q -> Page8Step6 q) -> Page8Step6 (Compose p (q ~> q)) #

Traversable Page8Step6 Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> Page8Step6 p -> m (Page8Step6 q) #

sequence :: forall m (p :: k -> Type). Applicative m => Page8Step6 (Compose m p) -> m (Page8Step6 p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (Page8Step6 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

showsPrec :: Int -> Page8Step6 line -> ShowS #

show :: Page8Step6 line -> String #

showList :: [Page8Step6 line] -> ShowS #

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (Page8Step6 line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: Page8Step6 line -> Page8Step6 line -> Bool #

(/=) :: Page8Step6 line -> Page8Step6 line -> Bool #

data TaxPreparer line Source #

Constructors

TaxPreparer 

Instances

Instances details
Applicative TaxPreparer Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

pure :: (forall (a :: k). f a) -> TaxPreparer f #

Apply TaxPreparer Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<*>) :: forall (p :: k -> Type) (q :: k -> Type). TaxPreparer (p ~> q) -> TaxPreparer p -> TaxPreparer q #

liftA2 :: (forall (a :: k). p a -> q a -> r a) -> TaxPreparer p -> TaxPreparer q -> TaxPreparer r #

liftA3 :: (forall (a :: k). p a -> q a -> r a -> s a) -> TaxPreparer p -> TaxPreparer q -> TaxPreparer r -> TaxPreparer s #

Distributive TaxPreparer Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collect :: forall p a (q :: k1 -> Type). Functor p => (a -> TaxPreparer q) -> p a -> TaxPreparer (Compose p q) #

distribute :: forall p (q :: k1 -> Type). Functor p => p (TaxPreparer q) -> TaxPreparer (Compose p q) #

cotraverse :: Functor m => (forall (a :: k1). m (p a) -> q a) -> m (TaxPreparer p) -> TaxPreparer q #

DistributiveTraversable TaxPreparer Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

collectTraversable :: forall f1 a (f2 :: k -> Type). Traversable f1 => (a -> TaxPreparer f2) -> f1 a -> TaxPreparer (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: k -> Type). Traversable f1 => f1 (TaxPreparer f2) -> TaxPreparer (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall (x :: k). f1 (f2 x) -> f x) -> f1 (TaxPreparer f2) -> TaxPreparer f #

Foldable TaxPreparer Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

foldMap :: Monoid m => (forall (a :: k). p a -> m) -> TaxPreparer p -> m #

Functor TaxPreparer Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(<$>) :: (forall (a :: k). p a -> q a) -> TaxPreparer p -> TaxPreparer q #

Logistic TaxPreparer Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

deliver :: forall p (q :: k1 -> Type). Contravariant p => p (TaxPreparer q -> TaxPreparer q) -> TaxPreparer (Compose p (q ~> q)) #

Traversable TaxPreparer Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

traverse :: Applicative m => (forall (a :: k). p a -> m (q a)) -> TaxPreparer p -> m (TaxPreparer q) #

sequence :: forall m (p :: k -> Type). Applicative m => TaxPreparer (Compose m p) -> m (TaxPreparer p) #

(Show (line Bool), Show (line Centi), Show (line Word), Show (line Text), Show (line Code), Show (line Day), Show (line LanguageOfCorrespondence), Show (line MaritalStatus)) => Show (TaxPreparer line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

showsPrec :: Int -> TaxPreparer line -> ShowS #

show :: TaxPreparer line -> String #

showList :: [TaxPreparer line] -> ShowS #

(Eq (line Bool), Eq (line Centi), Eq (line Word), Eq (line Text), Eq (line Code), Eq (line Day), Eq (line LanguageOfCorrespondence), Eq (line MaritalStatus)) => Eq (TaxPreparer line) Source # 
Instance details

Defined in Tax.Canada.T1.Types

Methods

(==) :: TaxPreparer line -> TaxPreparer line -> Bool #

(/=) :: TaxPreparer line -> TaxPreparer line -> Bool #