conjugate-programs-0.1.0.0
Safe HaskellNone
LanguageHaskell2010

Inference.Conjugate

Synopsis

Documentation

class Distribution a where Source #

Describes a family of distributions with a fixed form. For example, a Bernoulli distribution is parameterized by a probability p and produces binary samples (True with probability p, False with probability 1-p).

Its Distribution instance is: > instance Distribution Bernoulli where > type Params Bernoulli = Double > type Support Bernoulli = Bool > distSample _ = uncurry bernoulli > distLogP _ p True = log p > distLogP _ p False = log (1 - p)

Associated Types

type Params a Source #

type Support a Source #

Methods

distSample :: forall (m :: Type -> Type). PrimMonad m => a -> Params a -> Prob m (Support a) Source #

distLogP :: a -> Params a -> Support a -> Double Source #

Instances

Instances details
Distribution Bernoulli Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Params Bernoulli 
Instance details

Defined in Inference.Conjugate

type Support Bernoulli 
Instance details

Defined in Inference.Conjugate

Distribution Beta Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Params Beta 
Instance details

Defined in Inference.Conjugate

type Support Beta 
Instance details

Defined in Inference.Conjugate

Methods

distSample :: forall (m :: Type -> Type). PrimMonad m => Beta -> Params Beta -> Prob m (Support Beta) Source #

distLogP :: Beta -> Params Beta -> Support Beta -> Double Source #

Distribution Binomial Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Params Binomial 
Instance details

Defined in Inference.Conjugate

type Support Binomial 
Instance details

Defined in Inference.Conjugate

Distribution Geometric0 Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Params Geometric0 
Instance details

Defined in Inference.Conjugate

type Support Geometric0 
Instance details

Defined in Inference.Conjugate

Distribution Geometric1 Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Params Geometric1 
Instance details

Defined in Inference.Conjugate

type Support Geometric1 
Instance details

Defined in Inference.Conjugate

Distribution (Categorical n) Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Params (Categorical n) 
Instance details

Defined in Inference.Conjugate

type Params (Categorical n) = Vector Double
type Support (Categorical n) 
Instance details

Defined in Inference.Conjugate

Distribution (Dirichlet n) Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Params (Dirichlet n) 
Instance details

Defined in Inference.Conjugate

type Params (Dirichlet n) = Vector Double
type Support (Dirichlet n) 
Instance details

Defined in Inference.Conjugate

type Support (Dirichlet n) = Vector Double

Methods

distSample :: forall (m :: Type -> Type). PrimMonad m => Dirichlet n -> Params (Dirichlet n) -> Prob m (Support (Dirichlet n)) Source #

distLogP :: Dirichlet n -> Params (Dirichlet n) -> Support (Dirichlet n) -> Double Source #

newtype AsPrior p Source #

A type-level marker for treating a distribution as a prior.

Constructors

AsPrior p 

Instances

Instances details
Jeffreys (AsPrior Beta) Source # 
Instance details

Defined in Inference.Conjugate

KnownNat n => Jeffreys (AsPrior (Dirichlet n) :: Type) Source # 
Instance details

Defined in Inference.Conjugate

Prior (AsPrior Beta) Source # 
Instance details

Defined in Inference.Conjugate

Prior (AsPrior (Dirichlet n) :: Type) Source # 
Instance details

Defined in Inference.Conjugate

Uniform (AsPrior Beta) Source # 
Instance details

Defined in Inference.Conjugate

KnownNat n => Uniform (AsPrior (Dirichlet n) :: Type) Source # 
Instance details

Defined in Inference.Conjugate

type Hyper (AsPrior p :: Type) Source # 
Instance details

Defined in Inference.Conjugate

type Hyper (AsPrior p :: Type) = Params p
type Probs (AsPrior p :: Type) Source # 
Instance details

Defined in Inference.Conjugate

type Probs (AsPrior p :: Type) = Support p

class (Distribution p, Distribution l, Support p ~ Params l) => Conjugate p l where Source #

Marks two distributions as a conjugate pair of prior and likelihood. The property of such a pair is that the posterior has the same form as the prior (including the same Params and Support), and that its parameters can be obtained analytically from the parameters of the prior and a set of observations.

The class method updatePrior returns the parameters of the posterior given the prior parameters after a single observation.

Methods

priorSingleton Source #

Arguments

:: p

provides a singleton instance of the prior distribution in order to make sampling from priors easier.

updatePrior :: l -> Params p -> Support l -> Params p Source #

predLogP :: l -> Params p -> Support l -> Double Source #

Instances

Instances details
Conjugate Beta Bernoulli Source # 
Instance details

Defined in Inference.Conjugate

Conjugate Beta Binomial Source # 
Instance details

Defined in Inference.Conjugate

Conjugate Beta Geometric0 Source # 
Instance details

Defined in Inference.Conjugate

Conjugate Beta Geometric1 Source # 
Instance details

Defined in Inference.Conjugate

Conjugate (Dirichlet n) (Categorical n) Source # 
Instance details

Defined in Inference.Conjugate

type family Hyper (a :: k) Source #

Instances

Instances details
type Hyper (AsPrior p :: Type) Source # 
Instance details

Defined in Inference.Conjugate

type Hyper (AsPrior p :: Type) = Params p
type Hyper (a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Inference.Conjugate

type Hyper (a :: (Type -> Type) -> Type) = a HyperRep

type family Probs (a :: k) Source #

Instances

Instances details
type Probs (AsPrior p :: Type) Source # 
Instance details

Defined in Inference.Conjugate

type Probs (AsPrior p :: Type) = Support p
type Probs (a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Inference.Conjugate

type Probs (a :: (Type -> Type) -> Type) = a ProbsRep

newtype HyperRep p Source #

Constructors

HyperRep 

Fields

Instances

Instances details
Jeffreys (AsPrior p) => GJeffreys (K1 i (HyperRep p) :: k -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gjeffreysPrior :: forall (p0 :: k). K1 i (HyperRep p) p0 Source #

(Jeffreys k2, k2 HyperRep ~ Hyper k2) => GJeffreys (K1 i (k2 HyperRep) :: k1 -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gjeffreysPrior :: forall (p :: k1). K1 i (k2 HyperRep) p Source #

Uniform (AsPrior p) => GUniform (K1 i (HyperRep p) :: k -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

guniformPrior :: forall (p0 :: k). K1 i (HyperRep p) p0 Source #

(Uniform k2, k2 HyperRep ~ Hyper k2) => GUniform (K1 i (k2 HyperRep) :: k1 -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

guniformPrior :: forall (p :: k1). K1 i (k2 HyperRep) p Source #

Prior (AsPrior p) => GPrior (K1 i (HyperRep p) :: k -> Type) (K1 i (ProbsRep p) :: k -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gsampleProbs :: forall (m :: Type -> Type) (p0 :: k). PrimMonad m => K1 i (HyperRep p) p0 -> Prob m (K1 i (ProbsRep p) p0) Source #

gexpectedProbs :: forall (p0 :: k). K1 i (HyperRep p) p0 -> K1 i (ProbsRep p) p0 Source #

(Prior k2, k2 HyperRep ~ Hyper k2, k2 ProbsRep ~ Probs k2) => GPrior (K1 i (k2 HyperRep) :: k1 -> Type) (K1 i (k2 ProbsRep) :: k1 -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gsampleProbs :: forall (m :: Type -> Type) (p :: k1). PrimMonad m => K1 i (k2 HyperRep) p -> Prob m (K1 i (k2 ProbsRep) p) Source #

gexpectedProbs :: forall (p :: k1). K1 i (k2 HyperRep) p -> K1 i (k2 ProbsRep) p Source #

Show (Hyper (AsPrior p)) => Show (HyperRep p) Source # 
Instance details

Defined in Inference.Conjugate

Methods

showsPrec :: Int -> HyperRep p -> ShowS #

show :: HyperRep p -> String #

showList :: [HyperRep p] -> ShowS #

newtype ProbsRep p Source #

Constructors

ProbsRep 

Fields

Instances

Instances details
Prior (AsPrior p) => GPrior (K1 i (HyperRep p) :: k -> Type) (K1 i (ProbsRep p) :: k -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gsampleProbs :: forall (m :: Type -> Type) (p0 :: k). PrimMonad m => K1 i (HyperRep p) p0 -> Prob m (K1 i (ProbsRep p) p0) Source #

gexpectedProbs :: forall (p0 :: k). K1 i (HyperRep p) p0 -> K1 i (ProbsRep p) p0 Source #

(Prior k2, k2 HyperRep ~ Hyper k2, k2 ProbsRep ~ Probs k2) => GPrior (K1 i (k2 HyperRep) :: k1 -> Type) (K1 i (k2 ProbsRep) :: k1 -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gsampleProbs :: forall (m :: Type -> Type) (p :: k1). PrimMonad m => K1 i (k2 HyperRep) p -> Prob m (K1 i (k2 ProbsRep) p) Source #

gexpectedProbs :: forall (p :: k1). K1 i (k2 HyperRep) p -> K1 i (k2 ProbsRep) p Source #

Show (Probs (AsPrior p)) => Show (ProbsRep p) Source # 
Instance details

Defined in Inference.Conjugate

Methods

showsPrec :: Int -> ProbsRep p -> ShowS #

show :: ProbsRep p -> String #

showList :: [ProbsRep p] -> ShowS #

class Jeffreys (a :: k) where Source #

Instances

Instances details
Jeffreys (AsPrior Beta) Source # 
Instance details

Defined in Inference.Conjugate

KnownNat n => Jeffreys (AsPrior (Dirichlet n) :: Type) Source # 
Instance details

Defined in Inference.Conjugate

(Generic (t HyperRep), GJeffreys (Rep (t HyperRep))) => Jeffreys (t :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Inference.Conjugate

class GJeffreys (t :: k -> Type) where Source #

Methods

gjeffreysPrior :: forall (p :: k). t p Source #

Instances

Instances details
GJeffreys (U1 :: k -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gjeffreysPrior :: forall (p :: k). U1 p Source #

GJeffreys (V1 :: k -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gjeffreysPrior :: forall (p :: k). V1 p Source #

(GJeffreys ta, GJeffreys tb) => GJeffreys (ta :*: tb :: k -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gjeffreysPrior :: forall (p :: k). (ta :*: tb) p Source #

Jeffreys (AsPrior p) => GJeffreys (K1 i (HyperRep p) :: k -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gjeffreysPrior :: forall (p0 :: k). K1 i (HyperRep p) p0 Source #

(Jeffreys k2, k2 HyperRep ~ Hyper k2) => GJeffreys (K1 i (k2 HyperRep) :: k1 -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gjeffreysPrior :: forall (p :: k1). K1 i (k2 HyperRep) p Source #

GJeffreys t => GJeffreys (M1 i c t :: Type -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gjeffreysPrior :: M1 i c t p Source #

class Uniform (a :: k) where Source #

Instances

Instances details
Uniform (AsPrior Beta) Source # 
Instance details

Defined in Inference.Conjugate

KnownNat n => Uniform (AsPrior (Dirichlet n) :: Type) Source # 
Instance details

Defined in Inference.Conjugate

(Generic (t HyperRep), GUniform (Rep (t HyperRep))) => Uniform (t :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Inference.Conjugate

class GUniform (t :: k -> Type) where Source #

Methods

guniformPrior :: forall (p :: k). t p Source #

Instances

Instances details
GUniform (U1 :: k -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

guniformPrior :: forall (p :: k). U1 p Source #

GUniform (V1 :: k -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

guniformPrior :: forall (p :: k). V1 p Source #

(GUniform ta, GUniform tb) => GUniform (ta :*: tb :: k -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

guniformPrior :: forall (p :: k). (ta :*: tb) p Source #

Uniform (AsPrior p) => GUniform (K1 i (HyperRep p) :: k -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

guniformPrior :: forall (p0 :: k). K1 i (HyperRep p) p0 Source #

(Uniform k2, k2 HyperRep ~ Hyper k2) => GUniform (K1 i (k2 HyperRep) :: k1 -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

guniformPrior :: forall (p :: k1). K1 i (k2 HyperRep) p Source #

GUniform t => GUniform (M1 i c t :: Type -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

guniformPrior :: M1 i c t p Source #

class Prior (a :: k) where Source #

Methods

sampleProbs :: forall (m :: Type -> Type). PrimMonad m => Hyper a -> Prob m (Probs a) Source #

expectedProbs :: Hyper a -> Probs a Source #

Instances

Instances details
Prior (AsPrior Beta) Source # 
Instance details

Defined in Inference.Conjugate

Prior (AsPrior (Dirichlet n) :: Type) Source # 
Instance details

Defined in Inference.Conjugate

(Generic (a HyperRep), Generic (a ProbsRep), GPrior (Rep (a HyperRep)) (Rep (a ProbsRep))) => Prior (a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

sampleProbs :: forall (m :: Type -> Type). PrimMonad m => Hyper a -> Prob m (Probs a) Source #

expectedProbs :: Hyper a -> Probs a Source #

class GPrior (i :: k -> Type) (o :: k -> Type) where Source #

Methods

gsampleProbs :: forall (m :: Type -> Type) (p :: k). PrimMonad m => i p -> Prob m (o p) Source #

gexpectedProbs :: forall (p :: k). i p -> o p Source #

Instances

Instances details
GPrior (U1 :: k -> Type) (U1 :: k -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gsampleProbs :: forall (m :: Type -> Type) (p :: k). PrimMonad m => U1 p -> Prob m (U1 p) Source #

gexpectedProbs :: forall (p :: k). U1 p -> U1 p Source #

GPrior (V1 :: k -> Type) (V1 :: k -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gsampleProbs :: forall (m :: Type -> Type) (p :: k). PrimMonad m => V1 p -> Prob m (V1 p) Source #

gexpectedProbs :: forall (p :: k). V1 p -> V1 p Source #

(GPrior ia oa, GPrior ib ob) => GPrior (ia :*: ib :: k -> Type) (oa :*: ob :: k -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gsampleProbs :: forall (m :: Type -> Type) (p :: k). PrimMonad m => (ia :*: ib) p -> Prob m ((oa :*: ob) p) Source #

gexpectedProbs :: forall (p :: k). (ia :*: ib) p -> (oa :*: ob) p Source #

(GPrior ia oa, GPrior ib ob) => GPrior (ia :+: ib :: k -> Type) (oa :+: ob :: k -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gsampleProbs :: forall (m :: Type -> Type) (p :: k). PrimMonad m => (ia :+: ib) p -> Prob m ((oa :+: ob) p) Source #

gexpectedProbs :: forall (p :: k). (ia :+: ib) p -> (oa :+: ob) p Source #

Prior (AsPrior p) => GPrior (K1 i (HyperRep p) :: k -> Type) (K1 i (ProbsRep p) :: k -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gsampleProbs :: forall (m :: Type -> Type) (p0 :: k). PrimMonad m => K1 i (HyperRep p) p0 -> Prob m (K1 i (ProbsRep p) p0) Source #

gexpectedProbs :: forall (p0 :: k). K1 i (HyperRep p) p0 -> K1 i (ProbsRep p) p0 Source #

(Prior k2, k2 HyperRep ~ Hyper k2, k2 ProbsRep ~ Probs k2) => GPrior (K1 i (k2 HyperRep) :: k1 -> Type) (K1 i (k2 ProbsRep) :: k1 -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gsampleProbs :: forall (m :: Type -> Type) (p :: k1). PrimMonad m => K1 i (k2 HyperRep) p -> Prob m (K1 i (k2 ProbsRep) p) Source #

gexpectedProbs :: forall (p :: k1). K1 i (k2 HyperRep) p -> K1 i (k2 ProbsRep) p Source #

GPrior ti to => GPrior (M1 i c ti :: k -> Type) (M1 i' c' to :: k -> Type) Source # 
Instance details

Defined in Inference.Conjugate

Methods

gsampleProbs :: forall (m :: Type -> Type) (p :: k). PrimMonad m => M1 i c ti p -> Prob m (M1 i' c' to p) Source #

gexpectedProbs :: forall (p :: k). M1 i c ti p -> M1 i' c' to p Source #

type Accessor (r :: (k -> Type) -> Type) (p :: k) = forall (f :: k -> Type). Lens' (r f) (f p) Source #

class Monad m => RandomInterpreter (m :: Type -> Type) (r :: (Type -> Type) -> Type) | m -> r where Source #

Associated Types

type SampleCtx (m :: Type -> Type) a Source #

Methods

sampleValue :: (Conjugate p l, SampleCtx m l) => String -> l -> Accessor r p -> m (Support l) Source #

sampleConst :: (Distribution d, SampleCtx m d) => String -> d -> Params d -> m (Support d) Source #

permutationPlate :: Ord a => Int -> (Int -> m a) -> m [a] Source #

Instances

Instances details
RandomInterpreter (EvalPredTraceI r) r Source # 
Instance details

Defined in Inference.Conjugate

RandomInterpreter (EvalTraceI r) r Source # 
Instance details

Defined in Inference.Conjugate

RandomInterpreter (ShowTraceI r) r Source # 
Instance details

Defined in Inference.Conjugate

RandomInterpreter (TraceTraceI r) r Source # 
Instance details

Defined in Inference.Conjugate

RandomInterpreter (UpdatePriorsI r) r Source # 
Instance details

Defined in Inference.Conjugate

PrimMonad m => RandomInterpreter (SampleI m r) r Source # 
Instance details

Defined in Inference.Conjugate

Methods

sampleValue :: (Conjugate p l, SampleCtx (SampleI m r) l) => String -> l -> Accessor r p -> SampleI m r (Support l) Source #

sampleConst :: (Distribution d, SampleCtx (SampleI m r) d) => String -> d -> Params d -> SampleI m r (Support d) Source #

permutationPlate :: Ord a => Int -> (Int -> SampleI m r a) -> SampleI m r [a] Source #

PrimMonad m => RandomInterpreter (TraceI m r) r Source # 
Instance details

Defined in Inference.Conjugate

Methods

sampleValue :: (Conjugate p l, SampleCtx (TraceI m r) l) => String -> l -> Accessor r p -> TraceI m r (Support l) Source #

sampleConst :: (Distribution d, SampleCtx (TraceI m r) d) => String -> d -> Params d -> TraceI m r (Support d) Source #

permutationPlate :: Ord a => Int -> (Int -> TraceI m r a) -> TraceI m r [a] Source #

newtype Trace (r :: (Type -> Type) -> Type) Source #

Constructors

Trace 

Fields

Instances

Instances details
Show (Trace r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

showsPrec :: Int -> Trace r -> ShowS #

show :: Trace r -> String #

showList :: [Trace r] -> ShowS #

observeValue :: forall p l (m :: Type -> Type) (r :: (Type -> Type) -> Type). (Conjugate p l, Typeable (Support l), Monad m) => String -> l -> Accessor r p -> Support l -> StateT (Trace r) m () Source #

observeConst :: forall d (m :: Type -> Type) (r :: (Type -> Type) -> Type). (Distribution d, Typeable (Support d), Monad m) => String -> d -> Params d -> Support d -> StateT (Trace r) m () Source #

takeTrace :: forall a (r :: (Type -> Type) -> Type). Typeable a => Trace r -> Maybe ((String, a), Trace r) Source #

peekTrace :: forall (r :: (Type -> Type) -> Type). Trace r -> Maybe (String, Dynamic) Source #

newtype SampleI (m :: Type -> Type) (r :: (Type -> Type) -> Type) a Source #

Constructors

SampleI (ReaderT (r ProbsRep) (Prob m) a) 

Instances

Instances details
Monad m => Applicative (SampleI m r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

pure :: a -> SampleI m r a #

(<*>) :: SampleI m r (a -> b) -> SampleI m r a -> SampleI m r b #

liftA2 :: (a -> b -> c) -> SampleI m r a -> SampleI m r b -> SampleI m r c #

(*>) :: SampleI m r a -> SampleI m r b -> SampleI m r b #

(<*) :: SampleI m r a -> SampleI m r b -> SampleI m r a #

Functor m => Functor (SampleI m r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

fmap :: (a -> b) -> SampleI m r a -> SampleI m r b #

(<$) :: a -> SampleI m r b -> SampleI m r a #

Monad m => Monad (SampleI m r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

(>>=) :: SampleI m r a -> (a -> SampleI m r b) -> SampleI m r b #

(>>) :: SampleI m r a -> SampleI m r b -> SampleI m r b #

return :: a -> SampleI m r a #

PrimMonad m => RandomInterpreter (SampleI m r) r Source # 
Instance details

Defined in Inference.Conjugate

Methods

sampleValue :: (Conjugate p l, SampleCtx (SampleI m r) l) => String -> l -> Accessor r p -> SampleI m r (Support l) Source #

sampleConst :: (Distribution d, SampleCtx (SampleI m r) d) => String -> d -> Params d -> SampleI m r (Support d) Source #

permutationPlate :: Ord a => Int -> (Int -> SampleI m r a) -> SampleI m r [a] Source #

type SampleCtx (SampleI m r) a Source # 
Instance details

Defined in Inference.Conjugate

type SampleCtx (SampleI m r) a = ()

sampleResult :: p ProbsRep -> SampleI m p a -> Gen (PrimState m) -> m a Source #

newtype TraceI (m :: Type -> Type) (r :: (Type -> Type) -> Type) a Source #

Constructors

TraceI (ReaderT (r ProbsRep) (StateT (Trace r) (Prob m)) a) 

Instances

Instances details
Monad m => Applicative (TraceI m r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

pure :: a -> TraceI m r a #

(<*>) :: TraceI m r (a -> b) -> TraceI m r a -> TraceI m r b #

liftA2 :: (a -> b -> c) -> TraceI m r a -> TraceI m r b -> TraceI m r c #

(*>) :: TraceI m r a -> TraceI m r b -> TraceI m r b #

(<*) :: TraceI m r a -> TraceI m r b -> TraceI m r a #

Functor m => Functor (TraceI m r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

fmap :: (a -> b) -> TraceI m r a -> TraceI m r b #

(<$) :: a -> TraceI m r b -> TraceI m r a #

Monad m => Monad (TraceI m r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

(>>=) :: TraceI m r a -> (a -> TraceI m r b) -> TraceI m r b #

(>>) :: TraceI m r a -> TraceI m r b -> TraceI m r b #

return :: a -> TraceI m r a #

PrimMonad m => RandomInterpreter (TraceI m r) r Source # 
Instance details

Defined in Inference.Conjugate

Methods

sampleValue :: (Conjugate p l, SampleCtx (TraceI m r) l) => String -> l -> Accessor r p -> TraceI m r (Support l) Source #

sampleConst :: (Distribution d, SampleCtx (TraceI m r) d) => String -> d -> Params d -> TraceI m r (Support d) Source #

permutationPlate :: Ord a => Int -> (Int -> TraceI m r a) -> TraceI m r [a] Source #

type SampleCtx (TraceI m r) l Source # 
Instance details

Defined in Inference.Conjugate

type SampleCtx (TraceI m r) l = Typeable (Support l)

sampleTrace :: r ProbsRep -> TraceI m r a -> Gen (PrimState m) -> m (a, Trace r) Source #

newtype EvalTraceI (r :: (Type -> Type) -> Type) a Source #

Constructors

EvalTraceI (ReaderT (r ProbsRep) (StateT (Trace r, Double) Maybe) a) 

Instances

Instances details
Applicative (EvalTraceI r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

pure :: a -> EvalTraceI r a #

(<*>) :: EvalTraceI r (a -> b) -> EvalTraceI r a -> EvalTraceI r b #

liftA2 :: (a -> b -> c) -> EvalTraceI r a -> EvalTraceI r b -> EvalTraceI r c #

(*>) :: EvalTraceI r a -> EvalTraceI r b -> EvalTraceI r b #

(<*) :: EvalTraceI r a -> EvalTraceI r b -> EvalTraceI r a #

Functor (EvalTraceI r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

fmap :: (a -> b) -> EvalTraceI r a -> EvalTraceI r b #

(<$) :: a -> EvalTraceI r b -> EvalTraceI r a #

Monad (EvalTraceI r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

(>>=) :: EvalTraceI r a -> (a -> EvalTraceI r b) -> EvalTraceI r b #

(>>) :: EvalTraceI r a -> EvalTraceI r b -> EvalTraceI r b #

return :: a -> EvalTraceI r a #

RandomInterpreter (EvalTraceI r) r Source # 
Instance details

Defined in Inference.Conjugate

type SampleCtx (EvalTraceI r) l Source # 
Instance details

Defined in Inference.Conjugate

newtype EvalPredTraceI (r :: (Type -> Type) -> Type) a Source #

Constructors

EvalPredTraceI (ReaderT (r HyperRep) (StateT (Trace r, Double) Maybe) a) 

Instances

Instances details
Applicative (EvalPredTraceI r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

pure :: a -> EvalPredTraceI r a #

(<*>) :: EvalPredTraceI r (a -> b) -> EvalPredTraceI r a -> EvalPredTraceI r b #

liftA2 :: (a -> b -> c) -> EvalPredTraceI r a -> EvalPredTraceI r b -> EvalPredTraceI r c #

(*>) :: EvalPredTraceI r a -> EvalPredTraceI r b -> EvalPredTraceI r b #

(<*) :: EvalPredTraceI r a -> EvalPredTraceI r b -> EvalPredTraceI r a #

Functor (EvalPredTraceI r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

fmap :: (a -> b) -> EvalPredTraceI r a -> EvalPredTraceI r b #

(<$) :: a -> EvalPredTraceI r b -> EvalPredTraceI r a #

Monad (EvalPredTraceI r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

(>>=) :: EvalPredTraceI r a -> (a -> EvalPredTraceI r b) -> EvalPredTraceI r b #

(>>) :: EvalPredTraceI r a -> EvalPredTraceI r b -> EvalPredTraceI r b #

return :: a -> EvalPredTraceI r a #

RandomInterpreter (EvalPredTraceI r) r Source # 
Instance details

Defined in Inference.Conjugate

type SampleCtx (EvalPredTraceI r) l Source # 
Instance details

Defined in Inference.Conjugate

newtype UpdatePriorsI (r :: (Type -> Type) -> Type) a Source #

Constructors

UpdatePriorsI (StateT (Trace r, r HyperRep) Maybe a) 

Instances

Instances details
Applicative (UpdatePriorsI r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

pure :: a -> UpdatePriorsI r a #

(<*>) :: UpdatePriorsI r (a -> b) -> UpdatePriorsI r a -> UpdatePriorsI r b #

liftA2 :: (a -> b -> c) -> UpdatePriorsI r a -> UpdatePriorsI r b -> UpdatePriorsI r c #

(*>) :: UpdatePriorsI r a -> UpdatePriorsI r b -> UpdatePriorsI r b #

(<*) :: UpdatePriorsI r a -> UpdatePriorsI r b -> UpdatePriorsI r a #

Functor (UpdatePriorsI r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

fmap :: (a -> b) -> UpdatePriorsI r a -> UpdatePriorsI r b #

(<$) :: a -> UpdatePriorsI r b -> UpdatePriorsI r a #

Monad (UpdatePriorsI r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

(>>=) :: UpdatePriorsI r a -> (a -> UpdatePriorsI r b) -> UpdatePriorsI r b #

(>>) :: UpdatePriorsI r a -> UpdatePriorsI r b -> UpdatePriorsI r b #

return :: a -> UpdatePriorsI r a #

RandomInterpreter (UpdatePriorsI r) r Source # 
Instance details

Defined in Inference.Conjugate

type SampleCtx (UpdatePriorsI r) l Source # 
Instance details

Defined in Inference.Conjugate

newtype ShowTraceI (r :: (Type -> Type) -> Type) a Source #

Constructors

ShowTraceI (MaybeT (WriterT String (State (Trace r))) a) 

Instances

Instances details
Applicative (ShowTraceI r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

pure :: a -> ShowTraceI r a #

(<*>) :: ShowTraceI r (a -> b) -> ShowTraceI r a -> ShowTraceI r b #

liftA2 :: (a -> b -> c) -> ShowTraceI r a -> ShowTraceI r b -> ShowTraceI r c #

(*>) :: ShowTraceI r a -> ShowTraceI r b -> ShowTraceI r b #

(<*) :: ShowTraceI r a -> ShowTraceI r b -> ShowTraceI r a #

Functor (ShowTraceI r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

fmap :: (a -> b) -> ShowTraceI r a -> ShowTraceI r b #

(<$) :: a -> ShowTraceI r b -> ShowTraceI r a #

Monad (ShowTraceI r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

(>>=) :: ShowTraceI r a -> (a -> ShowTraceI r b) -> ShowTraceI r b #

(>>) :: ShowTraceI r a -> ShowTraceI r b -> ShowTraceI r b #

return :: a -> ShowTraceI r a #

RandomInterpreter (ShowTraceI r) r Source # 
Instance details

Defined in Inference.Conjugate

type SampleCtx (ShowTraceI r) l Source # 
Instance details

Defined in Inference.Conjugate

showTraceItem :: forall l (r :: (Type -> Type) -> Type). (Show (Support l), Typeable l, Typeable (Support l)) => String -> ShowTraceI r (Support l) Source #

showTrace :: forall (r :: (Type -> Type) -> Type) a. Trace r -> ShowTraceI r a -> (Maybe a, String) Source #

printTrace :: forall (r :: (Type -> Type) -> Type) a. Trace r -> ShowTraceI r a -> IO () Source #

newtype TraceTraceI (r :: (Type -> Type) -> Type) a Source #

Constructors

TraceTraceI (State (Trace r) a) 

Instances

Instances details
Applicative (TraceTraceI r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

pure :: a -> TraceTraceI r a #

(<*>) :: TraceTraceI r (a -> b) -> TraceTraceI r a -> TraceTraceI r b #

liftA2 :: (a -> b -> c) -> TraceTraceI r a -> TraceTraceI r b -> TraceTraceI r c #

(*>) :: TraceTraceI r a -> TraceTraceI r b -> TraceTraceI r b #

(<*) :: TraceTraceI r a -> TraceTraceI r b -> TraceTraceI r a #

Functor (TraceTraceI r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

fmap :: (a -> b) -> TraceTraceI r a -> TraceTraceI r b #

(<$) :: a -> TraceTraceI r b -> TraceTraceI r a #

Monad (TraceTraceI r) Source # 
Instance details

Defined in Inference.Conjugate

Methods

(>>=) :: TraceTraceI r a -> (a -> TraceTraceI r b) -> TraceTraceI r b #

(>>) :: TraceTraceI r a -> TraceTraceI r b -> TraceTraceI r b #

return :: a -> TraceTraceI r a #

RandomInterpreter (TraceTraceI r) r Source # 
Instance details

Defined in Inference.Conjugate

type SampleCtx (TraceTraceI r) l Source # 
Instance details

Defined in Inference.Conjugate

traceTraceItem :: forall l (r :: (Type -> Type) -> Type). (Show (Support l), Typeable l, Typeable (Support l)) => String -> TraceTraceI r (Support l) Source #

traceTrace :: forall (r :: (Type -> Type) -> Type) a. Trace r -> TraceTraceI r a -> a Source #

data Beta Source #

Constructors

Beta 

Instances

Instances details
Distribution Beta Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Params Beta 
Instance details

Defined in Inference.Conjugate

type Support Beta 
Instance details

Defined in Inference.Conjugate

Methods

distSample :: forall (m :: Type -> Type). PrimMonad m => Beta -> Params Beta -> Prob m (Support Beta) Source #

distLogP :: Beta -> Params Beta -> Support Beta -> Double Source #

Generic Beta Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Rep Beta 
Instance details

Defined in Inference.Conjugate

type Rep Beta = D1 ('MetaData "Beta" "Inference.Conjugate" "conjugate-programs-0.1.0.0-3yRv9wXBSRgCze1zWxB2WM" 'False) (C1 ('MetaCons "Beta" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Beta -> Rep Beta x #

to :: Rep Beta x -> Beta #

Show Beta Source # 
Instance details

Defined in Inference.Conjugate

Methods

showsPrec :: Int -> Beta -> ShowS #

show :: Beta -> String #

showList :: [Beta] -> ShowS #

Eq Beta Source # 
Instance details

Defined in Inference.Conjugate

Methods

(==) :: Beta -> Beta -> Bool #

(/=) :: Beta -> Beta -> Bool #

Ord Beta Source # 
Instance details

Defined in Inference.Conjugate

Methods

compare :: Beta -> Beta -> Ordering #

(<) :: Beta -> Beta -> Bool #

(<=) :: Beta -> Beta -> Bool #

(>) :: Beta -> Beta -> Bool #

(>=) :: Beta -> Beta -> Bool #

max :: Beta -> Beta -> Beta #

min :: Beta -> Beta -> Beta #

Conjugate Beta Bernoulli Source # 
Instance details

Defined in Inference.Conjugate

Conjugate Beta Binomial Source # 
Instance details

Defined in Inference.Conjugate

Conjugate Beta Geometric0 Source # 
Instance details

Defined in Inference.Conjugate

Conjugate Beta Geometric1 Source # 
Instance details

Defined in Inference.Conjugate

Jeffreys (AsPrior Beta) Source # 
Instance details

Defined in Inference.Conjugate

Prior (AsPrior Beta) Source # 
Instance details

Defined in Inference.Conjugate

Uniform (AsPrior Beta) Source # 
Instance details

Defined in Inference.Conjugate

type Params Beta Source # 
Instance details

Defined in Inference.Conjugate

type Support Beta Source # 
Instance details

Defined in Inference.Conjugate

type Rep Beta Source # 
Instance details

Defined in Inference.Conjugate

type Rep Beta = D1 ('MetaData "Beta" "Inference.Conjugate" "conjugate-programs-0.1.0.0-3yRv9wXBSRgCze1zWxB2WM" 'False) (C1 ('MetaCons "Beta" 'PrefixI 'False) (U1 :: Type -> Type))

data Bernoulli Source #

Constructors

Bernoulli 

Instances

Instances details
Distribution Bernoulli Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Params Bernoulli 
Instance details

Defined in Inference.Conjugate

type Support Bernoulli 
Instance details

Defined in Inference.Conjugate

Generic Bernoulli Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Rep Bernoulli 
Instance details

Defined in Inference.Conjugate

type Rep Bernoulli = D1 ('MetaData "Bernoulli" "Inference.Conjugate" "conjugate-programs-0.1.0.0-3yRv9wXBSRgCze1zWxB2WM" 'False) (C1 ('MetaCons "Bernoulli" 'PrefixI 'False) (U1 :: Type -> Type))
Show Bernoulli Source # 
Instance details

Defined in Inference.Conjugate

Eq Bernoulli Source # 
Instance details

Defined in Inference.Conjugate

Ord Bernoulli Source # 
Instance details

Defined in Inference.Conjugate

Conjugate Beta Bernoulli Source # 
Instance details

Defined in Inference.Conjugate

type Params Bernoulli Source # 
Instance details

Defined in Inference.Conjugate

type Support Bernoulli Source # 
Instance details

Defined in Inference.Conjugate

type Rep Bernoulli Source # 
Instance details

Defined in Inference.Conjugate

type Rep Bernoulli = D1 ('MetaData "Bernoulli" "Inference.Conjugate" "conjugate-programs-0.1.0.0-3yRv9wXBSRgCze1zWxB2WM" 'False) (C1 ('MetaCons "Bernoulli" 'PrefixI 'False) (U1 :: Type -> Type))

newtype Binomial Source #

Constructors

Binomial Int 

Instances

Instances details
Distribution Binomial Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Params Binomial 
Instance details

Defined in Inference.Conjugate

type Support Binomial 
Instance details

Defined in Inference.Conjugate

Generic Binomial Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Rep Binomial 
Instance details

Defined in Inference.Conjugate

type Rep Binomial = D1 ('MetaData "Binomial" "Inference.Conjugate" "conjugate-programs-0.1.0.0-3yRv9wXBSRgCze1zWxB2WM" 'True) (C1 ('MetaCons "Binomial" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

Methods

from :: Binomial -> Rep Binomial x #

to :: Rep Binomial x -> Binomial #

Show Binomial Source # 
Instance details

Defined in Inference.Conjugate

Eq Binomial Source # 
Instance details

Defined in Inference.Conjugate

Ord Binomial Source # 
Instance details

Defined in Inference.Conjugate

Conjugate Beta Binomial Source # 
Instance details

Defined in Inference.Conjugate

type Params Binomial Source # 
Instance details

Defined in Inference.Conjugate

type Support Binomial Source # 
Instance details

Defined in Inference.Conjugate

type Rep Binomial Source # 
Instance details

Defined in Inference.Conjugate

type Rep Binomial = D1 ('MetaData "Binomial" "Inference.Conjugate" "conjugate-programs-0.1.0.0-3yRv9wXBSRgCze1zWxB2WM" 'True) (C1 ('MetaCons "Binomial" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data Categorical (n :: Nat) Source #

Constructors

Categorical 

Instances

Instances details
Distribution (Categorical n) Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Params (Categorical n) 
Instance details

Defined in Inference.Conjugate

type Params (Categorical n) = Vector Double
type Support (Categorical n) 
Instance details

Defined in Inference.Conjugate

Generic (Categorical n) Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Rep (Categorical n) 
Instance details

Defined in Inference.Conjugate

type Rep (Categorical n) = D1 ('MetaData "Categorical" "Inference.Conjugate" "conjugate-programs-0.1.0.0-3yRv9wXBSRgCze1zWxB2WM" 'False) (C1 ('MetaCons "Categorical" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Categorical n -> Rep (Categorical n) x #

to :: Rep (Categorical n) x -> Categorical n #

Show (Categorical n) Source # 
Instance details

Defined in Inference.Conjugate

Eq (Categorical n) Source # 
Instance details

Defined in Inference.Conjugate

Ord (Categorical n) Source # 
Instance details

Defined in Inference.Conjugate

Conjugate (Dirichlet n) (Categorical n) Source # 
Instance details

Defined in Inference.Conjugate

type Params (Categorical n) Source # 
Instance details

Defined in Inference.Conjugate

type Params (Categorical n) = Vector Double
type Support (Categorical n) Source # 
Instance details

Defined in Inference.Conjugate

type Rep (Categorical n) Source # 
Instance details

Defined in Inference.Conjugate

type Rep (Categorical n) = D1 ('MetaData "Categorical" "Inference.Conjugate" "conjugate-programs-0.1.0.0-3yRv9wXBSRgCze1zWxB2WM" 'False) (C1 ('MetaCons "Categorical" 'PrefixI 'False) (U1 :: Type -> Type))

data Dirichlet (n :: Nat) Source #

Constructors

Dirichlet 

Instances

Instances details
KnownNat n => Jeffreys (AsPrior (Dirichlet n) :: Type) Source # 
Instance details

Defined in Inference.Conjugate

Prior (AsPrior (Dirichlet n) :: Type) Source # 
Instance details

Defined in Inference.Conjugate

KnownNat n => Uniform (AsPrior (Dirichlet n) :: Type) Source # 
Instance details

Defined in Inference.Conjugate

Distribution (Dirichlet n) Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Params (Dirichlet n) 
Instance details

Defined in Inference.Conjugate

type Params (Dirichlet n) = Vector Double
type Support (Dirichlet n) 
Instance details

Defined in Inference.Conjugate

type Support (Dirichlet n) = Vector Double

Methods

distSample :: forall (m :: Type -> Type). PrimMonad m => Dirichlet n -> Params (Dirichlet n) -> Prob m (Support (Dirichlet n)) Source #

distLogP :: Dirichlet n -> Params (Dirichlet n) -> Support (Dirichlet n) -> Double Source #

Generic (Dirichlet n) Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Rep (Dirichlet n) 
Instance details

Defined in Inference.Conjugate

type Rep (Dirichlet n) = D1 ('MetaData "Dirichlet" "Inference.Conjugate" "conjugate-programs-0.1.0.0-3yRv9wXBSRgCze1zWxB2WM" 'False) (C1 ('MetaCons "Dirichlet" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Dirichlet n -> Rep (Dirichlet n) x #

to :: Rep (Dirichlet n) x -> Dirichlet n #

Show (Dirichlet n) Source # 
Instance details

Defined in Inference.Conjugate

Eq (Dirichlet n) Source # 
Instance details

Defined in Inference.Conjugate

Methods

(==) :: Dirichlet n -> Dirichlet n -> Bool #

(/=) :: Dirichlet n -> Dirichlet n -> Bool #

Ord (Dirichlet n) Source # 
Instance details

Defined in Inference.Conjugate

Conjugate (Dirichlet n) (Categorical n) Source # 
Instance details

Defined in Inference.Conjugate

type Params (Dirichlet n) Source # 
Instance details

Defined in Inference.Conjugate

type Params (Dirichlet n) = Vector Double
type Support (Dirichlet n) Source # 
Instance details

Defined in Inference.Conjugate

type Support (Dirichlet n) = Vector Double
type Rep (Dirichlet n) Source # 
Instance details

Defined in Inference.Conjugate

type Rep (Dirichlet n) = D1 ('MetaData "Dirichlet" "Inference.Conjugate" "conjugate-programs-0.1.0.0-3yRv9wXBSRgCze1zWxB2WM" 'False) (C1 ('MetaCons "Dirichlet" 'PrefixI 'False) (U1 :: Type -> Type))

data Geometric0 Source #

Constructors

Geometric0 

Instances

Instances details
Distribution Geometric0 Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Params Geometric0 
Instance details

Defined in Inference.Conjugate

type Support Geometric0 
Instance details

Defined in Inference.Conjugate

Generic Geometric0 Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Rep Geometric0 
Instance details

Defined in Inference.Conjugate

type Rep Geometric0 = D1 ('MetaData "Geometric0" "Inference.Conjugate" "conjugate-programs-0.1.0.0-3yRv9wXBSRgCze1zWxB2WM" 'False) (C1 ('MetaCons "Geometric0" 'PrefixI 'False) (U1 :: Type -> Type))
Show Geometric0 Source # 
Instance details

Defined in Inference.Conjugate

Eq Geometric0 Source # 
Instance details

Defined in Inference.Conjugate

Ord Geometric0 Source # 
Instance details

Defined in Inference.Conjugate

Conjugate Beta Geometric0 Source # 
Instance details

Defined in Inference.Conjugate

type Params Geometric0 Source # 
Instance details

Defined in Inference.Conjugate

type Support Geometric0 Source # 
Instance details

Defined in Inference.Conjugate

type Rep Geometric0 Source # 
Instance details

Defined in Inference.Conjugate

type Rep Geometric0 = D1 ('MetaData "Geometric0" "Inference.Conjugate" "conjugate-programs-0.1.0.0-3yRv9wXBSRgCze1zWxB2WM" 'False) (C1 ('MetaCons "Geometric0" 'PrefixI 'False) (U1 :: Type -> Type))

data Geometric1 Source #

Constructors

Geometric1 

Instances

Instances details
Distribution Geometric1 Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Params Geometric1 
Instance details

Defined in Inference.Conjugate

type Support Geometric1 
Instance details

Defined in Inference.Conjugate

Generic Geometric1 Source # 
Instance details

Defined in Inference.Conjugate

Associated Types

type Rep Geometric1 
Instance details

Defined in Inference.Conjugate

type Rep Geometric1 = D1 ('MetaData "Geometric1" "Inference.Conjugate" "conjugate-programs-0.1.0.0-3yRv9wXBSRgCze1zWxB2WM" 'False) (C1 ('MetaCons "Geometric1" 'PrefixI 'False) (U1 :: Type -> Type))
Show Geometric1 Source # 
Instance details

Defined in Inference.Conjugate

Eq Geometric1 Source # 
Instance details

Defined in Inference.Conjugate

Ord Geometric1 Source # 
Instance details

Defined in Inference.Conjugate

Conjugate Beta Geometric1 Source # 
Instance details

Defined in Inference.Conjugate

type Params Geometric1 Source # 
Instance details

Defined in Inference.Conjugate

type Support Geometric1 Source # 
Instance details

Defined in Inference.Conjugate

type Rep Geometric1 Source # 
Instance details

Defined in Inference.Conjugate

type Rep Geometric1 = D1 ('MetaData "Geometric1" "Inference.Conjugate" "conjugate-programs-0.1.0.0-3yRv9wXBSRgCze1zWxB2WM" 'False) (C1 ('MetaCons "Geometric1" 'PrefixI 'False) (U1 :: Type -> Type))

replicateMWithI :: Applicative m => Int -> (Int -> m a) -> m [a] Source #