Skip to content

Commit

Permalink
Issue #12: Use global IDs that are unique for the entire duration of …
Browse files Browse the repository at this point in the history
…the program.

This will prevent cherry-picked history actions from having conflicting IDs.
  • Loading branch information
rgleichman committed Sep 21, 2020
1 parent 064aff1 commit 5cdfd12
Showing 1 changed file with 16 additions and 13 deletions.
29 changes: 16 additions & 13 deletions gui/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedStrings #-}
Expand Down Expand Up @@ -61,7 +62,7 @@ toMouseButton gtkMouseButton =
nodeSize :: (Double, Double)
nodeSize = (100, 40)

newtype ElemId = ElemId {_unElemId :: Int} deriving (Show, Eq, Ord)
newtype ElemId = ElemId {_unElemId :: Int} deriving (Show, Eq, Ord, Num)

-- | A graphical element that can be clicked
data Element = Element
Expand All @@ -88,7 +89,9 @@ data AppState = AppState
_asElements :: IntMap.IntMap Element,
-- | FPS rounded down to nearest hundred if over 200 fps.
_asFPSr :: Double,
_asHistory :: [HistoryEvent]
_asHistory :: [HistoryEvent],
_asBiggestID :: ElemId -- The biggest ElemId used so far in the
-- program. Not updated by undo.
}

data InputEvent
Expand All @@ -113,7 +116,8 @@ emptyAppState =
_asEdges = [],
_asElements = mempty,
_asFPSr = 0,
_asHistory = []
_asHistory = [],
_asBiggestID = 0
}

emptyInputs :: Inputs
Expand Down Expand Up @@ -234,20 +238,20 @@ clickOnNode elemId oldState@AppState {_asMovingNode, _asHistory} =

-- | Add a node to the canvas at the given position.
addNode :: (Double, Double) -> AppState -> AppState
addNode addPosition s@AppState {_asElements, _asHistory} =
let biggestKey = maybe 0 fst (IntMap.lookupMax _asElements)
newNode =
addNode addPosition state@AppState {_asElements, _asHistory, _asBiggestID} =
let newNode =
Element
{ _elPosition = addPosition,
_elSize = nodeSize,
_elZ = 0
}
nodeId = (biggestKey + 1)
nodeId = 1 + _asBiggestID
newElements =
IntMap.insert nodeId newNode _asElements
in s
IntMap.insert (_unElemId nodeId) newNode _asElements
in state
{ _asElements = newElements,
_asHistory = AddedNode (ElemId nodeId) : _asHistory
_asHistory = AddedNode nodeId : _asHistory,
_asBiggestID = nodeId
}

removeNode :: ElemId -> AppState -> AppState
Expand Down Expand Up @@ -390,7 +394,7 @@ backgroundPress inputsRef stateRef eventButton = do

addUndoInputAction :: IORef Inputs -> IO ()
addUndoInputAction inputsRef = do
putStrLn "Adding Undo input action."
putStrLn "Undo"
modifyIORef' inputsRef (addEvent Undo)
pure ()

Expand All @@ -400,9 +404,8 @@ keyPress inputsRef eventKey = do
-- getEventKeyState is ModifierTypeControlMask. May also want to use
-- Gdk.KEY_?.
key <- Gdk.getEventKeyString eventKey
print key
case key of
Just "\SUB" -> addUndoInputAction inputsRef -- putStrLn "ctrl-z pressed"
Just "\SUB" -> addUndoInputAction inputsRef -- ctrl-z pressed
_ -> pure ()
pure Gdk.EVENT_STOP

Expand Down

0 comments on commit 5cdfd12

Please sign in to comment.