Skip to content

Commit

Permalink
Merge pull request #267 from turion/dev_ghc96
Browse files Browse the repository at this point in the history
Allow 9.6
  • Loading branch information
turion authored Mar 5, 2024
2 parents 793843e + 5b00f1d commit d5689f5
Show file tree
Hide file tree
Showing 10 changed files with 40 additions and 14 deletions.
8 changes: 6 additions & 2 deletions benchmark/Single.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,12 @@
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE ImportQualifiedPost #-}

import Control.Applicative (Applicative (..))
import Control.Monad.Bayes.Sampler.Strict
import Data.Time (diffUTCTime, getCurrentTime)
import Helper
import Options.Applicative
( Applicative (liftA2),
ParserInfo,
( ParserInfo,
auto,
execParser,
fullDesc,
Expand All @@ -17,6 +17,10 @@ import Options.Applicative
option,
short,
)
-- Prelude exports liftA2 from GHC 9.6 on, see https://github.com/haskell/core-libraries-committee/blob/main/guides/export-lifta2-prelude.md
-- import Control.Applicative further up can be removed once we don't support GHC <= 9.4 anymore

import Prelude hiding (Applicative (..))

infer :: Model -> Alg -> IO ()
infer model alg = do
Expand Down
2 changes: 1 addition & 1 deletion flake.nix
Original file line number Diff line number Diff line change
Expand Up @@ -77,13 +77,13 @@
# https://github.com/tweag/monad-bayes/pull/256: Don't run tests on Mac because of machine precision issues
modifier = drv: if system == "x86_64-linux" then drv else pkgs.haskell.lib.dontCheck drv;
overrides = self: super: with pkgs.haskell.lib; { # Please check after flake.lock updates whether some of these overrides can be removed
hspec = super.hspec_2_11_7;
};
};
ghcs = [ # Always keep this up to date with the tested-with section in monad-bayes.cabal!
"ghc902"
"ghc927"
"ghc945"
"ghc964"
];
buildForVersion = ghcVersion: (builtins.getAttr ghcVersion pkgs.haskell.packages).developPackage opts;
in lib.attrsets.genAttrs ghcs buildForVersion;
Expand Down
7 changes: 5 additions & 2 deletions models/ConjugatePriors.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,12 +4,15 @@

module ConjugatePriors where

import Control.Applicative (Applicative (liftA2))
import Control.Applicative (Applicative (..))
import Control.Foldl (fold)
import Control.Foldl qualified as F
import Control.Monad.Bayes.Class (Bayesian (..), MonadDistribution (bernoulli, beta, gamma, normal), MonadMeasure, normalPdf)
import Numeric.Log (Log (Exp))
import Prelude
-- Prelude exports liftA2 from GHC 9.6 on, see https://github.com/haskell/core-libraries-committee/blob/main/guides/export-lifta2-prelude.md
-- import Control.Applicative further up can be removed once we don't support GHC <= 9.4 anymore

import Prelude hiding (Applicative (..))

type GammaParams = (Double, Double)

Expand Down
6 changes: 5 additions & 1 deletion models/Dice.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,13 +3,17 @@ module Dice (diceHard, diceSoft) where
-- A toy model for dice rolling from http://dl.acm.org/citation.cfm?id=2804317
-- Exact results can be obtained using Dist monad

import Control.Applicative (liftA2)
import Control.Applicative (Applicative (..))
import Control.Monad.Bayes.Class
( MonadDistribution (uniformD),
MonadFactor (score),
MonadMeasure,
condition,
)
-- Prelude exports liftA2 from GHC 9.6 on, see https://github.com/haskell/core-libraries-committee/blob/main/guides/export-lifta2-prelude.md
-- import Control.Applicative further up can be removed once we don't support GHC <= 9.4 anymore

import Prelude hiding (Applicative (..))

-- | A toss of a six-sided die.
die :: (MonadDistribution m) => m Int
Expand Down
8 changes: 4 additions & 4 deletions monad-bayes.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ copyright: 2015-2020 Adam Scibior
maintainer: [email protected]
author: Adam Scibior <[email protected]>
stability: experimental
tested-with: GHC ==9.0.2 || ==9.2.7 || ==9.4.5
tested-with: GHC ==9.0.2 || ==9.2.7 || ==9.4.5 || ==9.6.4
homepage: http://github.com/tweag/monad-bayes#readme
bug-reports: https://github.com/tweag/monad-bayes/issues
synopsis: A library for probabilistic programming.
Expand Down Expand Up @@ -38,7 +38,7 @@ flag dev

common deps
build-depends:
, base >=4.15 && <4.18
, base >=4.15 && <4.19
, brick >=1.0 && <2.0
, containers >=0.5.10 && <0.7
, foldl ^>=1.4
Expand All @@ -53,7 +53,7 @@ common deps
, matrix ^>=0.3
, monad-coroutine ^>=0.9.0
, monad-extras ^>=0.6
, mtl >=2.2 && <2.4
, mtl >=2.2.2 && <2.4
, mwc-random >=0.13.6 && <0.16
, pipes ^>=4.3
, pretty-simple ^>=4.1
Expand All @@ -72,7 +72,7 @@ common test-deps
, abstract-par ^>=0.3
, criterion >=1.5 && <1.7
, directory ^>=1.3
, hspec ^>=2.11
, hspec >=2.10 && <2.12
, monad-bayes
, optparse-applicative >=0.17 && <0.19
, process ^>=1.6
Expand Down
4 changes: 3 additions & 1 deletion src/Control/Monad/Bayes/Enumerator.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,16 +32,18 @@ where

import Control.Applicative (Alternative)
import Control.Arrow (second)
import Control.Monad (MonadPlus)
import Control.Monad.Bayes.Class
( MonadDistribution (bernoulli, categorical, logCategorical, random),
MonadFactor (..),
MonadMeasure,
)
import Control.Monad.Writer
import Control.Monad.Writer (WriterT (..))
import Data.AEq (AEq, (===), (~==))
import Data.List (sortOn)
import Data.Map qualified as Map
import Data.Maybe (fromMaybe)
import Data.Monoid (Product (..))
import Data.Ord (Down (Down))
import Data.Vector qualified as VV
import Data.Vector.Generic qualified as V
Expand Down
4 changes: 4 additions & 0 deletions src/Control/Monad/Bayes/Integrator.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,6 +48,10 @@ import Numeric.Integration.TanhSinh (Result (result), trap)
import Numeric.Log (Log (ln))
import Statistics.Distribution qualified as Statistics
import Statistics.Distribution.Uniform qualified as Statistics
-- Prelude exports liftA2 from GHC 9.6 on, see https://github.com/haskell/core-libraries-committee/blob/main/guides/export-lifta2-prelude.md
-- import Control.Applicative further up can be removed once we don't support GHC <= 9.4 anymore

import Prelude hiding (Applicative (..))

newtype Integrator a = Integrator {getIntegrator :: Cont Double a}
deriving newtype (Functor, Applicative, Monad)
Expand Down
3 changes: 2 additions & 1 deletion src/Control/Monad/Bayes/Sampler/Lazy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,10 +7,11 @@
-- | This is a port of the implementation of LazyPPL: https://lazyppl.bitbucket.io/
module Control.Monad.Bayes.Sampler.Lazy where

import Control.Monad (ap)
import Control.Monad.Bayes.Class (MonadDistribution (random))
import Control.Monad.Bayes.Weighted (WeightedT, runWeightedT)
import Control.Monad.IO.Class
import Control.Monad.Identity
import Control.Monad.Identity (Identity (runIdentity))
import Control.Monad.Trans
import Numeric.Log (Log (..))
import System.Random
Expand Down
6 changes: 5 additions & 1 deletion src/Control/Monad/Bayes/Traced/Basic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ module Control.Monad.Bayes.Traced.Basic
)
where

import Control.Applicative (liftA2)
import Control.Applicative (Applicative (..))
import Control.Monad.Bayes.Class
( MonadDistribution (random),
MonadFactor (..),
Expand All @@ -34,6 +34,10 @@ import Control.Monad.Bayes.Traced.Common
import Control.Monad.Bayes.Weighted (WeightedT)
import Data.Functor.Identity (Identity)
import Data.List.NonEmpty as NE (NonEmpty ((:|)), toList)
-- Prelude exports liftA2 from GHC 9.6 on, see https://github.com/haskell/core-libraries-committee/blob/main/guides/export-lifta2-prelude.md
-- import Control.Applicative further up can be removed once we don't support GHC <= 9.4 anymore

import Prelude hiding (Applicative (..))

-- | Tracing monad that records random choices made in the program.
data TracedT m a = TracedT
Expand Down
6 changes: 5 additions & 1 deletion src/Control/Monad/Bayes/Traced/Static.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ module Control.Monad.Bayes.Traced.Static
)
where

import Control.Applicative (liftA2)
import Control.Applicative (Applicative (..))
import Control.Monad.Bayes.Class
( MonadDistribution (random),
MonadFactor (..),
Expand All @@ -35,6 +35,10 @@ import Control.Monad.Bayes.Traced.Common
import Control.Monad.Bayes.Weighted (WeightedT)
import Control.Monad.Trans (MonadTrans (..))
import Data.List.NonEmpty as NE (NonEmpty ((:|)), toList)
-- Prelude exports liftA2 from GHC 9.6 on, see https://github.com/haskell/core-libraries-committee/blob/main/guides/export-lifta2-prelude.md
-- import Control.Applicative further up can be removed once we don't support GHC <= 9.4 anymore

import Prelude hiding (Applicative (..))

-- | A tracing monad where only a subset of random choices are traced.
--
Expand Down

0 comments on commit d5689f5

Please sign in to comment.