Skip to content

Commit

Permalink
Preparation for GHC-9.0 (#78)
Browse files Browse the repository at this point in the history
This fixes some would-be warnings in GHC-9.0
that we're going to switch to once
#76 is merged.
  • Loading branch information
basvandijk authored May 20, 2022
1 parent 80e14e3 commit b7bbd5d
Show file tree
Hide file tree
Showing 3 changed files with 6 additions and 5 deletions.
3 changes: 2 additions & 1 deletion src/IC/Purify.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,11 +7,12 @@ module IC.Purify where

import Control.Monad.ST
import Data.Functor
import Data.Kind (Type)
import Data.Either
import Data.Bifunctor

class SnapshotAble i where
type SnapshotOf i :: *
type SnapshotOf i :: Type
persist :: i s -> ST s (SnapshotOf i)
recreate :: SnapshotOf i -> ST s (i s)

Expand Down
3 changes: 1 addition & 2 deletions src/IC/Test/Agent.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,6 @@ import Numeric.Natural
import Data.Char
import Test.Tasty.HUnit
import Test.Tasty.Options
import Control.Monad.Trans
import Control.Monad.Except
import Control.Concurrent
import Control.Exception (catch)
Expand Down Expand Up @@ -128,7 +127,7 @@ connect :: String -> Int -> IO ReplWrapper
connect ep tp = do
agentConfig <- makeAgentConfig ep tp
let ?agentConfig = agentConfig
return (R id)
return (R $ \x -> x)

-- Yes, implicit arguments are frowned upon. But they are also very useful.

Expand Down
5 changes: 3 additions & 2 deletions src/IC/Wasm/Winter/Persist.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ import qualified Data.IntMap as IM
import qualified Data.Map.Lazy as M
import qualified Data.Vector as V
import Data.ByteString.Lazy (ByteString)
import Data.Kind (Type)

import qualified IC.Canister.StableMemory as Stable

Expand Down Expand Up @@ -56,8 +57,8 @@ resumeMemory :: W.MemoryInst (ST s) -> ByteString -> ST s ()
resumeMemory i p = resume i p

class Monad (M a) => Persistable a where
type Persisted a :: *
type M a :: * -> *
type Persisted a :: Type
type M a :: Type -> Type
persist :: a -> M a (Persisted a)
resume :: a -> Persisted a -> M a ()

Expand Down

0 comments on commit b7bbd5d

Please sign in to comment.