Skip to content

Commit

Permalink
🧩 [refactor]: Partial roll out of new design.
Browse files Browse the repository at this point in the history
  • Loading branch information
rolyp committed Oct 3, 2023
1 parent 1cc92d4 commit ec2b779
Show file tree
Hide file tree
Showing 4 changed files with 16 additions and 18 deletions.
14 changes: 10 additions & 4 deletions src/Module.purs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ import Control.Monad.Error.Class (liftEither, throwError)
import Control.Monad.Except (class MonadError)
import Data.Either (Either(..))
import Data.HTTP.Method (Method(..))
import Data.List (List(..), (:))
import Data.List (List(..), reverse, (:))
import Data.Newtype (class Newtype)
import Data.Set (empty)
import Data.Traversable (traverse)
Expand All @@ -20,6 +20,7 @@ import Effect.Aff.Class (class MonadAff, liftAff)
import Effect.Exception (Error)
import Effect.Exception (error) as E
import EvalGraph (GraphConfig, eval, eval_module)
import Expr (Module)
import Graph (class Graph, Vertex)
import Graph (empty) as G
import Graph.GraphWriter (class MonadWithGraphAlloc, alloc, fresh, runWithGraphAllocT)
Expand Down Expand Up @@ -73,13 +74,13 @@ defaultImports = do
>>= loadModule (File "graphics")
>>= loadModule (File "convolution")

loadModule2 :: forall m. MonadAff m => MonadWithGraphAlloc m => File -> Raw ProgCxt -> m (Raw ProgCxt)
loadModule2 :: forall m. MonadAff m => MonadError Error m => File -> Raw ProgCxt -> m (Raw ProgCxt)
loadModule2 file (ProgCxt r@{ mods }) = do
src <- loadFile (Folder "fluid/lib") file
mod <- parse src module_ >>= desugarModuleFwd
pure $ ProgCxt r { mods = mod : mods }

defaultImports2 :: forall m. MonadAff m => MonadWithGraphAlloc m => m (Raw ProgCxt)
defaultImports2 :: forall m. MonadAff m => MonadError Error m => m (Raw ProgCxt)
defaultImports2 =
loadModule2 (File "prelude") (ProgCxt { mods: Nil, datasets: Nil })
>>= loadModule2 (File "graphics")
Expand Down Expand Up @@ -108,4 +109,9 @@ openDatasetAs file x { g, n, progCxt: ProgCxtEval r@{ progCxt: ProgCxt r'@{ data
eval_progCxt :: forall m. MonadWithGraphAlloc m => ProgCxt Vertex -> m (Env Vertex)
eval_progCxt (ProgCxt { mods }) = do
traverse alloc primitives
>>= concatM (mods <#> \mod γ' -> eval_module γ' mod empty)
>>= concatM (reverse mods <#> addDefs)
where
addDefs :: Module Vertex -> Env Vertex -> m (Env Vertex)
addDefs mod γ = do
γ' <- eval_module γ mod empty
pure $ γ <+> γ'
2 changes: 1 addition & 1 deletion src/Val.purs
Original file line number Diff line number Diff line change
Expand Up @@ -79,7 +79,7 @@ newtype ProgCxtEval a = ProgCxtEval
}

newtype ProgCxt a = ProgCxt
{ mods :: List (Module a)
{ mods :: List (Module a) -- in reverse order
, datasets :: List (Expr a)
}

Expand Down
10 changes: 1 addition & 9 deletions test/Main.purs
Original file line number Diff line number Diff line change
@@ -1,12 +1,4 @@
module Test.Main
( main
, test_bwd
, test_desugaring
, test_graphics
-- , test_linking
, test_misc
-- , test_scratchpad
) where
module Test.Main where

import Prelude hiding (add)

Expand Down
8 changes: 4 additions & 4 deletions test/Many.purs
Original file line number Diff line number Diff line change
Expand Up @@ -6,17 +6,17 @@ import App.Fig (linkResult, loadLinkFig)
import Benchmark.Util (BenchRow)
import Data.Array (zip)
import Effect.Aff (Aff)
import Module (File(..), Folder(..), loadFile, openDatasetAs, openDefaultImports)
import Test.Util (TestBwdSpec, TestLinkSpec, TestSpec, TestWithDatasetSpec, checkPretty, testWithSetup)
import Module (File(..), Folder(..), defaultImports2, loadFile, openDatasetAs, openDefaultImports)
import Test.Util (TestBwdSpec, TestLinkSpec, TestSpec, TestWithDatasetSpec, checkPretty, testWithSetup, testWithSetup2)
import Util (type (×), (×))
import Val (ProgCxtEval(..), (<+>))

many :: Array TestSpec -> Int -> Array (String × Aff BenchRow)
many specs n = zip (specs <#> _.file) (specs <#> one)
where
one { file, fwd_expect } = do
gconfig <- openDefaultImports
testWithSetup n (File file) gconfig { δv: identity, fwd_expect, bwd_expect: mempty }
progCxt <- defaultImports2
testWithSetup2 n (File file) progCxt { δv: identity, fwd_expect, bwd_expect: mempty }

bwdMany :: Array TestBwdSpec -> Int -> Array (String × Aff BenchRow)
bwdMany specs n = zip (specs <#> _.file) (specs <#> bwdOne)
Expand Down

0 comments on commit ec2b779

Please sign in to comment.