Skip to content
This repository has been archived by the owner on Jun 18, 2023. It is now read-only.

Commit

Permalink
feat(core): improved layout generation
Browse files Browse the repository at this point in the history
  • Loading branch information
prescientmoon committed Oct 19, 2020
1 parent f250690 commit 72068c9
Show file tree
Hide file tree
Showing 3 changed files with 27 additions and 20 deletions.
9 changes: 9 additions & 0 deletions packages/core/src/Ast.purs
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ module Lunarflow.Ast
, lambda
, var
, printDeBrujin
, isVar
) where

import Prelude
Expand Down Expand Up @@ -118,3 +119,11 @@ printDeBrujin = para algebra
Call _ (Tuple funcAst func) (Tuple argAst arg) ->
parenthesiseWhen (needsParenthesis true $ project funcAst) func
<> parenthesiseWhen (needsParenthesis false $ project argAst) arg

-- | Check if an expression is a var
isVar :: forall v c l. Ast v c l -> Boolean
isVar =
project
>>> case _ of
Var _ -> true
_ -> false
1 change: 1 addition & 0 deletions packages/core/src/Ast/Grouped.purs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@ import Data.Set as Set
import Lunarflow.Ast (AstF(..), Expression, call, lambda, var)
import Matryoshka (Algebra, cata, project)

-- TODO: Make the argument list nonempty.
-- | The base functor for grouped expressions.
type GroupedExpressionF
= AstF Int Unit (List.List String)
Expand Down
37 changes: 17 additions & 20 deletions packages/core/src/Layout.purs
Original file line number Diff line number Diff line change
Expand Up @@ -115,7 +115,17 @@ addIndices = para algebra
position <- getVarPosition index
in var { index, position }
Call _ (Tuple _ layoutFunction) (Tuple groupedArgument layoutArgument) -> do
inArgument <- usedPositions groupedArgument
let
-- This type annotation is here so the compiler
-- knows which Unfoldable instance to use.
vars :: Array _
vars = Set.toUnfoldable $ references groupedArgument
-- This holds all the variables referenced inside the argument of the call
inArgument <- Set.fromFoldable <$> for vars getVarPosition
-- When we draw a call, we draw the function first and then the argument.
-- We don't want the space taken by the variables in the argument to be occupied
-- by stuff while drawing the function.
-- So we basically inform the call not to touch those spaces.
function <- protect inArgument layoutFunction
argument <- layoutArgument
ado
Expand All @@ -129,9 +139,11 @@ addIndices = para algebra
{ body', args } <-
local (_ { currentScope = scope }) do
args <-
forWithIndex vars \index name -> ado
position <- newPosition (varCount - 1 - index)
in { name, position }
forWithIndex vars \index name -> do
state <- getState
setState state { indexMap = List.snoc state.indexMap (varCount - 1 - index) }
position <- mkPosition $ List.length state.indexMap
pure { name, position }
let
updateCtx ctx =
ctx
Expand All @@ -146,7 +158,7 @@ addIndices = para algebra
where
varCount = List.length vars

protect :: forall a. Set.Set Position -> LayoutM a -> LayoutM a
protect :: Set.Set Position -> LayoutM ~> LayoutM
protect inputs = local (\a -> a { protected = a.protected <> inputs })

getPosition :: ScopedLayout -> Position
Expand All @@ -169,12 +181,6 @@ addIndices = para algebra
scope <- asks _.currentScope
pure $ Position index scope

newPosition :: Int -> LayoutM Position
newPosition index = do
state <- getState
setState state { indexMap = state.indexMap <> pure index }
mkPosition $ List.length state.indexMap

everywhere :: Set.Set Position -> LayoutM Position
everywhere exclude = do
state <- getState
Expand Down Expand Up @@ -231,15 +237,6 @@ addIndices = para algebra
Just position -> pure position
Nothing -> empty

usedPositions :: GroupedExpression -> LayoutM (Set.Set Position)
usedPositions expression = do
let
-- This type annotation is here so the compiler
-- knows which Unfoldable instance to use.
vars :: Array _
vars = Set.toUnfoldable $ references expression
Set.fromFoldable <$> for vars getVarPosition

-- | Run the computations represented by a LayoutM monad.
runLayoutM :: forall a. LayoutM a -> List.List (Tuple a IndexMap)
runLayoutM m = evalState noListT def
Expand Down

0 comments on commit 72068c9

Please sign in to comment.