From 767b4937c2ee7b0af6a9fe90a479f94f6fc603e0 Mon Sep 17 00:00:00 2001 From: Hans-Peter Deifel <hpd@hpdeifel.de> Date: Fri, 9 Nov 2018 13:42:37 +0100 Subject: [PATCH] Rename a few type variables from h to f --- src/Copar/Algorithm.hs | 2 +- src/Copar/Algorithm/Initialize.hs | 8 ++++---- src/Copar/Algorithm/Split.hs | 18 +++++++++--------- src/Copar/Algorithm/Types.hs | 8 ++++---- src/Copar/Coalgebra/RefinementTypes.hs | 8 ++++---- src/Copar/RefinementInterface.hs | 6 +++--- src/main/Main.hs | 2 +- tests/Copar/Algorithm/SplitSpec.hs | 8 ++++---- tests/Copar/Coalgebra/ParserSpec.hs | 2 +- 9 files changed, 31 insertions(+), 31 deletions(-) diff --git a/src/Copar/Algorithm.hs b/src/Copar/Algorithm.hs index c38e1c9..8619356 100644 --- a/src/Copar/Algorithm.hs +++ b/src/Copar/Algorithm.hs @@ -31,7 +31,7 @@ data AlgoStatistics = AlgoStatistics } -- | Returns the count of 'split' calls -processQueue :: RefinementInterface h => BlockQueue s -> AlgoState s h -> ST s Int +processQueue :: RefinementInterface f => BlockQueue s -> AlgoState s f -> ST s Int processQueue queue as = do count <- newSTRef 0 whileM $ Queue.dequeue queue >>= \case diff --git a/src/Copar/Algorithm/Initialize.hs b/src/Copar/Algorithm/Initialize.hs index bf0bdcb..b8e4c19 100644 --- a/src/Copar/Algorithm/Initialize.hs +++ b/src/Copar/Algorithm/Initialize.hs @@ -22,9 +22,9 @@ import Copar.Coalgebra.RefinementTypes import qualified Data.RefinablePartition as Partition -- returns (initial queue content, algo state) -initialize :: forall h s. RefinementInterface h - => Encoding (Label h) (F1 h) - -> ST s ([Block], AlgoState s h) +initialize :: forall f s. RefinementInterface f + => Encoding (Label f) (F1 f) + -> ST s ([Block], AlgoState s f) initialize encoding = do toSub <- VM.replicate (size encoding) [] lastW <- VM.new (numEdges encoding) @@ -39,7 +39,7 @@ initialize encoding = do forM_ (states encoding) $ \x -> do outgoingLabels <- VM.read toSub x >>= mapM (\(!x) -> let !l = label (graph encoding x) in return l) - px <- newSTRef $! RI.init @h (typeOf encoding x) outgoingLabels + px <- newSTRef $! RI.init @f (typeOf encoding x) outgoingLabels VM.read toSub x >>= mapM_ (\(EdgeRef e) -> VM.write lastW e px) VM.write toSub x [] diff --git a/src/Copar/Algorithm/Split.hs b/src/Copar/Algorithm/Split.hs index 33bc17b..dd893aa 100644 --- a/src/Copar/Algorithm/Split.hs +++ b/src/Copar/Algorithm/Split.hs @@ -46,9 +46,9 @@ import qualified Copar.RefinementInterface as RI import Copar.Coalgebra.RefinementTypes import Copar.Algorithm.Types -type SplitM s h = ReaderT (AlgoState s h, BlockQueue s) (ST s) +type SplitM s f = ReaderT (AlgoState s f, BlockQueue s) (ST s) -split :: RefinementInterface h => Block -> SplitM s h () +split :: RefinementInterface f => Block -> SplitM s f () split blockS = do (as, _) <- ask touchedBlocks <- collectTouchedBlocks blockS @@ -66,7 +66,7 @@ split blockS = do -- values returned from 'update' are saved in @h3Cache@. -- -- As a precondition, toSub must not be empty for marked states. -updateBlock :: forall s h. RefinementInterface h => Block -> F3 h -> SplitM s h () +updateBlock :: forall s f. RefinementInterface f => Block -> F3 f -> SplitM s f () updateBlock b v0 = ask >>= \(as, _) -> lift $ do markB <- Partition.markedStates (partition as) b VU.forM_ markB $ \x -> do @@ -79,7 +79,7 @@ updateBlock b v0 = ask >>= \(as, _) -> lift $ do let Edge _ !lab _ = graph (encoding as) e return $! lab) - (!wxS, !vx, !wxCwithoutS) <- RI.update @h labelsToS <$> readSTRef pc + (!wxS, !vx, !wxCwithoutS) <- RI.update @f labelsToS <$> readSTRef pc writeSTRef pc wxCwithoutS !ps <- newSTRef wxS @@ -97,7 +97,7 @@ updateBlock b v0 = ask >>= \(as, _) -> lift $ do -- @b@ must have at least one marked state -- -- Returns a list of new sub-blocks of @b@ -splitBlock :: RefinementInterface h => Block -> SplitM s h [Block] +splitBlock :: RefinementInterface f => Block -> SplitM s f [Block] splitBlock b = ask >>= \(as, _) -> lift $ do -- b has marked states, so b1 is guaranteed to be non-empty (Just b1, bunmarked) <- Partition.splitMarked (partition as) b @@ -130,10 +130,10 @@ splitBlock b = ask >>= \(as, _) -> lift $ do -- -- Runtime: @O(|sub-blocks|)@ addBlocksToQueue - :: RefinementInterface h + :: RefinementInterface f => Block -- ^ Original super-block -> [Block] -- ^ List of split-off sub-blocks - -> SplitM s h () + -> SplitM s f () addBlocksToQueue b blocks = ask >>= \(as, queue) -> lift $ do bInQueue <- Queue.elem b queue @@ -150,7 +150,7 @@ addBlocksToQueue b blocks = ask >>= \(as, queue) -> lift $ do -- -- Such predecessor states are marked for subsequent splitting and their edges -- into @S@ are added to @toSub@. -collectTouchedBlocks :: forall s h. RefinementInterface h => Block -> SplitM s h [(Block, F3 h)] +collectTouchedBlocks :: forall s f. RefinementInterface f => Block -> SplitM s f [(Block, F3 f)] collectTouchedBlocks blockS = do (as, _) <- ask @@ -165,7 +165,7 @@ collectTouchedBlocks blockS = do unlessM ((==1) <$> Partition.blockSize (partition as) b) $ do unlessM (Partition.hasMarked (partition as) b) $ do wCx <- readSTRef =<< VM.read (lastW as) (fromEdgeRef e) - let v0 = snd3 $ RI.update @h [] wCx + let v0 = snd3 $ RI.update @f [] wCx modifySTRef markedBlocks ((b, v0):) whenM (null <$> VM.read (toSub as) x) $ diff --git a/src/Copar/Algorithm/Types.hs b/src/Copar/Algorithm/Types.hs index 4e68b09..ae2c759 100644 --- a/src/Copar/Algorithm/Types.hs +++ b/src/Copar/Algorithm/Types.hs @@ -23,13 +23,13 @@ import Data.MorphismEncoding import Data.RefinablePartition ( RefinablePartition ) import Copar.Coalgebra.RefinementTypes -data AlgoState s h = AlgoState +data AlgoState s f = AlgoState { toSub :: {-# UNPACK #-} (MVector s [EdgeRef]) - , lastW :: {-# UNPACK #-} (MVector s (STRef s (Weight h))) - , encoding :: {-# UNPACK #-} (Encoding (Label h) (F1 h)) + , lastW :: {-# UNPACK #-} (MVector s (STRef s (Weight f))) + , encoding :: {-# UNPACK #-} (Encoding (Label f) (F1 f)) , pred :: {-# UNPACK #-} (Vector [EdgeRef]) , partition :: {-# UNPACK #-} (RefinablePartition s) - , h3Cache :: {-# UNPACK #-} (MVector s (F3 h)) + , h3Cache :: {-# UNPACK #-} (MVector s (F3 f)) } makeLensesFor diff --git a/src/Copar/Coalgebra/RefinementTypes.hs b/src/Copar/Coalgebra/RefinementTypes.hs index d49b20d..fc684bc 100644 --- a/src/Copar/Coalgebra/RefinementTypes.hs +++ b/src/Copar/Coalgebra/RefinementTypes.hs @@ -5,7 +5,7 @@ module Copar.Coalgebra.RefinementTypes , F3 ) where -type family Label (h :: * -> *) :: * -type family Weight (h :: * -> *) :: * -type family F1 (h :: * -> *) :: * -type family F3 (h :: * -> *) :: * +type family Label (f :: * -> *) :: * +type family Weight (f :: * -> *) :: * +type family F1 (f :: * -> *) :: * +type family F3 (f :: * -> *) :: * diff --git a/src/Copar/RefinementInterface.hs b/src/Copar/RefinementInterface.hs index 264ef28..db439c9 100644 --- a/src/Copar/RefinementInterface.hs +++ b/src/Copar/RefinementInterface.hs @@ -5,7 +5,7 @@ module Copar.RefinementInterface where import Copar.Coalgebra.RefinementTypes -class (Ord (F1 h), Ord (F3 h)) => RefinementInterface (h :: * -> *) +class (Ord (F1 f), Ord (F3 f)) => RefinementInterface (f :: * -> *) where - init :: F1 h -> [Label h] -> Weight h - update :: [Label h] -> Weight h -> (Weight h, F3 h, Weight h) + init :: F1 f -> [Label f] -> Weight f + update :: [Label f] -> Weight f -> (Weight f, F3 f, Weight f) diff --git a/src/main/Main.hs b/src/main/Main.hs index 76f2d03..4ced26b 100644 --- a/src/main/Main.hs +++ b/src/main/Main.hs @@ -334,7 +334,7 @@ main = do info (options <**> helper) fullDesc case optCommand params of - (HelpCommand h) -> printHelp h + (HelpCommand f) -> printHelp f (RefineCommand r) -> do stats <- initStats (refineStats r) (refineStatsJson r) diff --git a/tests/Copar/Algorithm/SplitSpec.hs b/tests/Copar/Algorithm/SplitSpec.hs index 719abee..1d81c76 100644 --- a/tests/Copar/Algorithm/SplitSpec.hs +++ b/tests/Copar/Algorithm/SplitSpec.hs @@ -277,9 +277,9 @@ splitSpec = describe "split" $ do ) withState - :: RefinementInterface h - => Encoding (Label h) (F1 h) - -> (forall s . SplitM s h a) + :: RefinementInterface f + => Encoding (Label f) (F1 f) + -> (forall s . SplitM s f a) -> a withState e action = runST $ do (q, as) <- initialize e @@ -287,7 +287,7 @@ withState e action = runST $ do mapM_ (Queue.enqueue queue) q runSplit as queue action -runSplit :: AlgoState s h -> BlockQueue s -> SplitM s h a -> ST s a +runSplit :: AlgoState s f -> BlockQueue s -> SplitM s f a -> ST s a runSplit as queue action = runReaderT action (as, queue) enc :: [h1] -> [(State, label, State)] -> Encoding label h1 diff --git a/tests/Copar/Coalgebra/ParserSpec.hs b/tests/Copar/Coalgebra/ParserSpec.hs index 3241b6e..530dc49 100644 --- a/tests/Copar/Coalgebra/ParserSpec.hs +++ b/tests/Copar/Coalgebra/ParserSpec.hs @@ -168,7 +168,7 @@ instance Eq SomeLabel where Just HRefl -> a == b data SomeF1 where - SomeF1 :: forall h. (Show h, Eq h, Typeable h) => h -> SomeF1 + SomeF1 :: forall f. (Show f, Eq f, Typeable f) => f -> SomeF1 deriving instance Show SomeF1 -- GitLab