10
10
-}
11
11
12
12
{-# LANGUAGE CPP #-}
13
+ {-# LANGUAGE FlexibleContexts #-}
13
14
{-# LANGUAGE OverloadedStrings #-}
14
15
{-# LANGUAGE QuasiQuotes #-}
15
16
{-# LANGUAGE TemplateHaskell #-}
16
17
17
18
module Clash.Normalize where
18
19
20
+ import qualified Control.Concurrent.Async.Lifted as Async
21
+ import Control.Concurrent.MVar.Lifted (MVar )
19
22
import qualified Control.Concurrent.MVar.Lifted as MVar
20
23
import Control.Concurrent.Supply (Supply )
21
24
import Control.Exception (throw )
22
25
import qualified Control.Lens as Lens
23
26
import Control.Monad (when )
27
+ import qualified Control.Monad.IO.Class as Monad (liftIO )
24
28
import Control.Monad.State.Strict (State )
25
29
import Data.Default (def )
26
30
import Data.Either (lefts ,partitionEithers )
@@ -64,7 +68,7 @@ import Clash.Core.Var (Id, varName, varType)
64
68
import Clash.Core.VarEnv
65
69
(VarEnv , elemVarSet , eltsVarEnv , emptyInScopeSet , emptyVarEnv ,
66
70
extendVarEnv , lookupVarEnv , mapVarEnv , mapMaybeVarEnv ,
67
- mkVarEnv , mkVarSet , notElemVarEnv , notElemVarSet , nullVarEnv , unionVarEnv )
71
+ mkVarEnv , mkVarSet , notElemVarEnv , notElemVarSet , nullVarEnv )
68
72
import Clash.Debug (traceIf )
69
73
import Clash.Driver.Types
70
74
(BindingMap , Binding (.. ), DebugOpts (.. ), ClashEnv (.. ))
@@ -79,7 +83,7 @@ import Clash.Normalize.Util
79
83
import Clash.Rewrite.Combinators ((>->) ,(!->) ,repeatR ,topdownR )
80
84
import Clash.Rewrite.Types
81
85
(RewriteEnv (.. ), RewriteState (.. ), bindings , debugOpts , extra ,
82
- tcCache , topEntities , newInlineStrategy )
86
+ tcCache , topEntities , newInlineStrategy , ioLock )
83
87
import Clash.Rewrite.Util
84
88
(apply , isUntranslatableType , runRewriteSession )
85
89
import Clash.Util
@@ -89,10 +93,8 @@ import Data.Binary (encode)
89
93
import qualified Data.ByteString as BS
90
94
import qualified Data.ByteString.Lazy as BL
91
95
92
- import System.IO.Unsafe (unsafePerformIO )
93
96
import Clash.Rewrite.Types (RewriteStep (.. ))
94
97
95
-
96
98
-- | Run a NormalizeSession in a given environment
97
99
runNormalization
98
100
:: ClashEnv
@@ -109,12 +111,14 @@ runNormalization
109
111
-- ^ Hardcoded evaluator for WHNF (old evaluator)
110
112
-> VarEnv Bool
111
113
-- ^ Map telling whether a components is part of a recursive group
114
+ -> MVar ()
115
+ -- ^ Synchronization on stdout
112
116
-> [Id ]
113
117
-- ^ topEntities
114
118
-> NormalizeSession a
115
119
-- ^ NormalizeSession to run
116
120
-> IO a
117
- runNormalization env supply globals typeTrans peEval eval rcsMap entities session = do
121
+ runNormalization env supply globals typeTrans peEval eval rcsMap lock entities session = do
118
122
normState <- NormalizeState
119
123
<$> MVar. newMVar emptyVarEnv
120
124
<*> MVar. newMVar Map. empty
@@ -131,6 +135,7 @@ runNormalization env supply globals typeTrans peEval eval rcsMap entities sessio
131
135
<*> MVar. newMVar 0
132
136
<*> MVar. newMVar (mempty , 0 )
133
137
<*> MVar. newMVar emptyVarEnv
138
+ <*> pure lock
134
139
<*> pure normState
135
140
136
141
runRewriteSession rwEnv rwState session
@@ -143,20 +148,17 @@ runNormalization env supply globals typeTrans peEval eval rcsMap entities sessio
143
148
, _topEntities = mkVarSet entities
144
149
}
145
150
146
- normalize
147
- :: [Id ]
148
- -> NormalizeSession BindingMap
149
- normalize [] = return emptyVarEnv
150
- normalize top = do
151
- (new,topNormalized) <- unzip <$> mapM normalize' top
152
- newNormalized <- normalize (concat new)
153
- return (unionVarEnv (mkVarEnv topNormalized) newNormalized)
151
+ normalize :: [Id ] -> NormalizeSession BindingMap
152
+ normalize tops = do
153
+ normBinds <- Async. mapConcurrently normalize' tops
154
+ pure (mkVarEnv (concat normBinds))
154
155
155
- normalize' :: Id -> NormalizeSession ([ Id ], (Id , Binding Term ))
156
+ normalize' :: Id -> NormalizeSession [ (Id , Binding Term )]
156
157
normalize' nm = do
157
158
bndrsV <- Lens. use bindings
158
159
exprM <- MVar. withMVar bndrsV (pure . lookupVarEnv nm)
159
160
let nmS = showPpr (varName nm)
161
+ -- traceM ("normalize: start " <> nmS)
160
162
case exprM of
161
163
Just (Binding nm' sp inl pr tm r) -> do
162
164
tcm <- Lens. view tcCache
@@ -196,11 +198,17 @@ normalize' nm = do
196
198
197
199
normV <- Lens. use (extra. normalized)
198
200
199
- MVar. withMVar normV $ \ norm ->
200
- let prevNorm = mapVarEnv bindingId norm
201
- toNormalize = filter (`notElemVarSet` topEnts)
202
- $ filter (`notElemVarEnv` extendVarEnv nm nm prevNorm) usedBndrs
203
- in return (toNormalize,(nm,tmNorm))
201
+ toNormalize <-
202
+ MVar. withMVar normV $ \ norm ->
203
+ let prevNorm = mapVarEnv bindingId norm
204
+ toNormalize = filter (`notElemVarSet` topEnts)
205
+ $ filter (`notElemVarEnv` extendVarEnv nm nm prevNorm) usedBndrs
206
+ in pure toNormalize
207
+
208
+ -- traceM ("normalize: end: " <> nmS)
209
+
210
+ normChildren <- Async. mapConcurrently normalize' toNormalize
211
+ return ((nm, tmNorm) : concat normChildren)
204
212
else
205
213
do
206
214
-- Throw an error for unrepresentable topEntities and functions
@@ -222,7 +230,7 @@ normalize' nm = do
222
230
, showPpr (coreTypeOf nm')
223
231
, " ) has a non-representable return type."
224
232
, " Not normalising:\n " , showPpr tm] )
225
- (return ( [] , (nm,(Binding nm' sp inl pr tm r))) )
233
+ (return [ (nm,(Binding nm' sp inl pr tm r))] )
226
234
227
235
228
236
Nothing -> error $ $ (curLoc) ++ " Expr belonging to bndr: " ++ nmS ++ " not found"
@@ -354,18 +362,22 @@ flattenCallTree (CBranch (nm,(Binding nm' sp inl pr tm r)) used) = do
354
362
-- NB: When -fclash-debug-history is on, emit binary data holding the recorded rewrite steps
355
363
opts <- Lens. view debugOpts
356
364
let rewriteHistFile = dbg_historyFile opts
357
- when (Maybe. isJust rewriteHistFile) $
358
- let ! _ = unsafePerformIO
359
- $ BS. appendFile (Maybe. fromJust rewriteHistFile)
360
- $ BL. toStrict
361
- $ encode RewriteStep
362
- { t_ctx = []
363
- , t_name = " INLINE"
364
- , t_bndrS = showPpr (varName nm')
365
- , t_before = tm
366
- , t_after = tm1
367
- }
368
- in pure ()
365
+
366
+ when (Maybe. isJust rewriteHistFile) $ do
367
+ lock <- Lens. use ioLock
368
+
369
+ MVar. withMVar lock $ \ () ->
370
+ Monad. liftIO
371
+ . BS. appendFile (Maybe. fromJust rewriteHistFile)
372
+ . BL. toStrict
373
+ $ encode RewriteStep
374
+ { t_ctx = []
375
+ , t_name = " INLINE"
376
+ , t_bndrS = showPpr (varName nm')
377
+ , t_before = tm
378
+ , t_after = tm1
379
+ }
380
+
369
381
rewriteExpr (" flattenExpr" ,flatten) (showPpr nm, tm1) (nm', sp)
370
382
let allUsed = newUsed ++ concat il_used
371
383
-- inline all components when the resulting expression after flattening
0 commit comments