Skip to content

Commit

Permalink
fix bottom panel
Browse files Browse the repository at this point in the history
  • Loading branch information
shmish111 committed Oct 22, 2020
1 parent fc6ea72 commit 262b2d1
Show file tree
Hide file tree
Showing 5 changed files with 11 additions and 18 deletions.
6 changes: 3 additions & 3 deletions marlowe-playground-client/src/HaskellEditor/View.purs
@@ -1,10 +1,11 @@
module HaskellEditor.View where

import Prelude hiding (div)

import Data.Array as Array
import Data.Either (Either(..))
import Data.Enum (toEnum, upFromIncluding)
import Data.Lens (has, is, to, view, (^.))
import Data.Lens (has, to, view, (^.))
import Data.Maybe (Maybe(..), fromMaybe)
import Data.String (Pattern(..), split)
import Data.String as String
Expand All @@ -24,7 +25,7 @@ import LocalStorage as LocalStorage
import Monaco (getModel, setValue) as Monaco
import Network.RemoteData (RemoteData(..), _Loading, isLoading, isSuccess)
import StaticData as StaticData
import Types (ChildSlots, _haskellEditorSlot, bottomPanelHeight)
import Types (ChildSlots, _haskellEditorSlot)

render ::
forall m.
Expand Down Expand Up @@ -92,7 +93,6 @@ bottomPanel state =
else
[ analysisPanel, collapsed ]
)
, bottomPanelHeight showingBottomPanel
]
)
[ div
Expand Down
6 changes: 2 additions & 4 deletions marlowe-playground-client/src/JSEditor.purs
@@ -1,6 +1,5 @@
module JSEditor where

import Data.Array ((:))
import Data.Array as Array
import Data.Enum (toEnum, upFromIncluding)
import Data.Lens (to, view, (^.))
Expand All @@ -13,7 +12,7 @@ import Halogen (ClassName(..), ComponentHTML, liftEffect)
import Halogen.Classes (aHorizontal, analysisPanel, closeDrawerArrowIcon, codeEditor, collapsed, footerPanelBg, minimizeIcon)
import Halogen.HTML (HTML, a, button, code_, div, div_, img, option, pre_, section, select, slot, text)
import Halogen.HTML.Events (onClick, onSelectedIndexChange)
import Halogen.HTML.Properties (alt, class_, classes, enabled, href, src)
import Halogen.HTML.Properties (alt, class_, classes, href, src)
import Halogen.HTML.Properties as HTML
import Halogen.Monaco (monacoComponent)
import Language.Javascript.Interpreter (CompilationError(..), InterpreterResult(..))
Expand All @@ -23,7 +22,7 @@ import Monaco as Monaco
import Prelude (bind, bottom, const, map, not, show, unit, ($), (<$>), (<<<), (<>), (==))
import StaticData as StaticData
import Text.Pretty (pretty)
import Types (Action(..), ChildSlots, FrontendState, JSCompilationState(..), _jsCompilationResult, _jsEditorKeybindings, _jsEditorSlot, _showBottomPanel, bottomPanelHeight)
import Types (Action(..), ChildSlots, FrontendState, JSCompilationState(..), _jsCompilationResult, _jsEditorKeybindings, _jsEditorSlot, _showBottomPanel)

render ::
forall m.
Expand Down Expand Up @@ -95,7 +94,6 @@ bottomPanel state =
else
[ analysisPanel, collapsed ]
)
, bottomPanelHeight showingBottomPanel
]
)
[ div
Expand Down
2 changes: 0 additions & 2 deletions marlowe-playground-client/src/Simulation/BottomPanel.purs
Expand Up @@ -31,7 +31,6 @@ import Servant.PureScript.Ajax (AjaxError(..), ErrorDescription(..))
import Simulation.State (MarloweEvent(..), _contract, _editorErrors, _editorWarnings, _log, _slot, _state, _transactionError, _transactionWarnings)
import Simulation.Types (Action(..), AnalysisState(..), BottomPanelView(..), ReachabilityAnalysisData(..), State, _analysisState, _bottomPanelView, _marloweState, _showBottomPanel, _showErrorDetail, isContractValid)
import Text.Parsing.StringParser.Basic (lines)
import Types (bottomPanelHeight)

bottomPanel :: forall p. State -> HTML p Action
bottomPanel state =
Expand All @@ -42,7 +41,6 @@ bottomPanel state =
else
[ ClassName "simulation-bottom-panel", collapsed ]
)
-- , bottomPanelHeight showingBottomPanel
]
)
[ div [ classes [ flex, ClassName "flip-x", ClassName "full-height" ] ]
Expand Down
11 changes: 2 additions & 9 deletions marlowe-playground-client/src/Types.purs
Expand Up @@ -15,12 +15,11 @@ import Data.Symbol (SProxy(..))
import Demos.Types as Demos
import Gist (Gist, GistId)
import Gists (GistAction)
import Halogen (AttrName(..), ClassName)
import Halogen (ClassName)
import Halogen as H
import Halogen.ActusBlockly as AB
import Halogen.Blockly (BlocklyMessage, BlocklyQuery)
import Halogen.Classes (activeClass)
import Halogen.HTML (IProp, attr)
import Halogen.Monaco (KeyBindings)
import Halogen.Monaco as Monaco
import HaskellEditor.Types as HE
Expand Down Expand Up @@ -271,10 +270,4 @@ _value :: forall s a. Lens' { value :: a | s } a
_value = prop (SProxy :: SProxy "value")

isActiveTab :: FrontendState -> View -> Array ClassName
isActiveTab state activeView = state ^. _view <<< (activeClass (eq activeView))

-- TODO: https://github.com/purescript-halogen/purescript-halogen/issues/682
bottomPanelHeight :: forall r i. Boolean -> IProp r i
bottomPanelHeight true = attr (AttrName "style") ""

bottomPanelHeight false = attr (AttrName "style") "height: 3.5rem"
isActiveTab state activeView = state ^. _view <<< (activeClass (eq activeView))
4 changes: 4 additions & 0 deletions marlowe-playground-client/static/css/panels.scss
Expand Up @@ -296,6 +296,10 @@ button.minus-btn:hover {
box-shadow: var(--box-shadow-inverted);
}

.analysis-panel.collapsed {
height: 8em;
}

.simulation-bottom-panel {
position: absolute;
width: 67%;
Expand Down

0 comments on commit 262b2d1

Please sign in to comment.