Skip to content

Commit

Permalink
Make it build with mtl 2.3 (#131)
Browse files Browse the repository at this point in the history
`mtl` no longer re-exports some common monad functions so import them
from their place
  • Loading branch information
albertov authored Jul 25, 2024
1 parent 3c376b2 commit 2cb89d0
Show file tree
Hide file tree
Showing 10 changed files with 29 additions and 18 deletions.
3 changes: 3 additions & 0 deletions inferno-core/CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,9 @@
# Revision History for inferno-core
*Note*: we use https://pvp.haskell.org/ (MAJOR.MAJOR.MINOR.PATCH)

## 0.11.6.0 -- 2024-07-25
* mtl 2.3 compatibility

## 0.11.5.1 -- 2024-04-26
* Fix pretty print of Some/None pattern in error messages

Expand Down
4 changes: 2 additions & 2 deletions inferno-core/inferno-core.cabal
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
cabal-version: 2.4
name: inferno-core
version: 0.11.5.1
version: 0.11.6.0
synopsis: A statically-typed functional scripting language
description: Parser, type inference, and interpreter for a statically-typed functional scripting language
category: DSL,Scripting
Expand Down Expand Up @@ -63,7 +63,7 @@ library
, inferno-types >= 0.4.0 && < 0.5
, megaparsec >= 9.2.1 && < 9.3
, memory >= 0.18.0 && < 0.19
, mtl >= 2.2.2 && < 2.3
, mtl >= 2.2.2 && < 2.4
, parser-combinators >= 1.3.0 && < 1.4
, picosat >= 0.1.6 && < 0.2
, prettyprinter >= 1.7.1 && < 1.8
Expand Down
2 changes: 1 addition & 1 deletion inferno-core/src/Inferno/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module Inferno.Core where

import Control.Monad (foldM)
import Control.Monad.Catch (MonadCatch, MonadThrow)
import Control.Monad.Except (MonadFix)
import Control.Monad.Fix (MonadFix)
import Data.Bifunctor (bimap, first)
import Data.List.NonEmpty (NonEmpty)
import qualified Data.Map as Map
Expand Down
2 changes: 1 addition & 1 deletion inferno-core/src/Inferno/Eval.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,8 @@

module Inferno.Eval where

import Control.Monad (forM)
import Control.Monad.Catch (MonadCatch, MonadThrow (throwM), try)
import Control.Monad.Except (forM)
import Control.Monad.Reader (ask, local)
import Data.Foldable (foldrM)
import Data.Functor ((<&>))
Expand Down
10 changes: 6 additions & 4 deletions inferno-core/src/Inferno/Infer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,14 +16,16 @@ module Inferno.Infer
)
where

import Control.Monad (when)
import Control.Monad
( foldM,
forM,
forM_,
when,
)
import Control.Monad.Except
( Except,
ExceptT,
MonadError (catchError, throwError),
foldM,
forM,
forM_,
runExcept,
runExceptT,
)
Expand Down
1 change: 1 addition & 0 deletions inferno-core/src/Inferno/Instances/Arbitrary.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

Expand Down
3 changes: 2 additions & 1 deletion inferno-core/src/Inferno/Utils/QQ/Script.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ module Inferno.Utils.QQ.Script where
import Control.Monad.Catch (MonadCatch (..), MonadThrow (..))
import Control.Monad.IO.Class (MonadIO)
import Control.Monad.Reader (ReaderT (..))
import Control.Monad.Writer (WriterT (..), appEndo)
import Control.Monad.Writer (WriterT (..))
import qualified Crypto.Hash as Crypto
import Data.ByteArray (convert)
import Data.ByteString (ByteString, unpack)
Expand All @@ -17,6 +17,7 @@ import Data.Generics.Aliases (extQ)
import Data.List (intercalate)
import qualified Data.List.NonEmpty as NEList
import qualified Data.Maybe as Maybe
import Data.Monoid (appEndo)
import Data.Text (pack)
import Inferno.Infer (inferExpr)
import Inferno.Infer.Pinned (pinExpr)
Expand Down
3 changes: 3 additions & 0 deletions inferno-types/CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,9 @@
# Revision History for inferno-types
*Note*: we use https://pvp.haskell.org/ (MAJOR.MAJOR.MINOR.PATCH)

## 0.4.6.0 -- 2024-07-25
* mtl 2.3 compatibility

## 0.4.5.0 -- 2024-04-26
* Add `unusedVars` method for `Expr`s and tests for it

Expand Down
4 changes: 2 additions & 2 deletions inferno-types/inferno-types.cabal
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
cabal-version: >=1.10
name: inferno-types
version: 0.4.5.0
version: 0.4.6.0
synopsis: Core types for Inferno
description: Core types for the Inferno language
category: DSL,Scripting
Expand Down Expand Up @@ -43,7 +43,7 @@ library
, hashable >= 1.4.1 && < 1.5
, megaparsec >= 9.2.1 && < 9.3
, memory >= 0.18.0 && < 0.19
, mtl >= 2.2.2 && < 2.3
, mtl >= 2.2.2 && < 2.4
, prettyprinter >= 1.7.1 && < 1.8
, recursion-schemes >= 5.2.2.3 && < 5.3
, servant >= 0.19 && < 0.20
Expand Down
15 changes: 8 additions & 7 deletions inferno-types/src/Inferno/Types/Value.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,10 +6,11 @@ module Inferno.Types.Value where

import Control.DeepSeq (NFData, rnf)
import Control.Monad.Catch (MonadCatch (..), MonadThrow (..))
import Control.Monad.Except (MonadError, lift)
import Control.Monad.Except (MonadError)
import Control.Monad.Fix (MonadFix)
import Control.Monad.IO.Class (MonadIO)
import Control.Monad.Reader (MonadReader, ReaderT (..))
import Control.Monad.Trans (lift)
import Data.Int (Int64)
import qualified Data.Map as Map
import Data.Text (Text)
Expand Down Expand Up @@ -51,7 +52,7 @@ data Value custom m
| VTypeRep InfernoType
| VCustom custom

instance NFData custom => NFData (Value custom m) where
instance (NFData custom) => NFData (Value custom m) where
rnf (VInt x) = x `seq` ()
rnf (VDouble x) = x `seq` ()
rnf (VWord16 x) = x `seq` ()
Expand All @@ -69,7 +70,7 @@ instance NFData custom => NFData (Value custom m) where
rnf (VTypeRep x) = rnf x
rnf (VCustom x) = rnf x

instance Eq c => Eq (Value c m) where
instance (Eq c) => Eq (Value c m) where
(VInt i1) == (VInt i2) = i1 == i2
(VDouble v1) == (VDouble v2) = v1 == v2
(VWord16 w1) == (VWord16 w2) = w1 == w2
Expand All @@ -88,7 +89,7 @@ instance Eq c => Eq (Value c m) where
(VCustom c1) == (VCustom c2) = c1 == c2
_ == _ = False

instance Pretty c => Pretty (Value c m) where
instance (Pretty c) => Pretty (Value c m) where
pretty = \case
VInt n -> pretty n
VDouble n -> pretty n
Expand All @@ -113,14 +114,14 @@ instance Pretty c => Pretty (Value c m) where
newtype ImplEnvM m c a = ImplEnvM {unImplEnvM :: ReaderT (Map.Map ExtIdent (Value c (ImplEnvM m c))) m a}
deriving (Applicative, Functor, Monad, MonadReader (Map.Map ExtIdent (Value c (ImplEnvM m c))), MonadError e, MonadFix, MonadIO)

instance MonadThrow m => MonadThrow (ImplEnvM m c) where
instance (MonadThrow m) => MonadThrow (ImplEnvM m c) where
throwM = ImplEnvM . lift . throwM

instance MonadCatch m => MonadCatch (ImplEnvM m c) where
instance (MonadCatch m) => MonadCatch (ImplEnvM m c) where
catch (ImplEnvM (ReaderT m)) c = ImplEnvM $ ReaderT $ \env ->
m env `catch` \e -> runImplEnvM env (c e)

liftImplEnvM :: Monad m => m a -> ImplEnvM m c a
liftImplEnvM :: (Monad m) => m a -> ImplEnvM m c a
liftImplEnvM = ImplEnvM . lift

runImplEnvM :: Map.Map ExtIdent (Value c (ImplEnvM m c)) -> ImplEnvM m c a -> m a
Expand Down

0 comments on commit 2cb89d0

Please sign in to comment.