Skip to content

Commit

Permalink
Update source code to latest APIs.
Browse files Browse the repository at this point in the history
  • Loading branch information
FranklinChen committed May 13, 2017
1 parent a731f90 commit b47d427
Show file tree
Hide file tree
Showing 4 changed files with 13 additions and 16 deletions.
11 changes: 5 additions & 6 deletions src/DOMHelper.purs
Original file line number Diff line number Diff line change
Expand Up @@ -16,8 +16,8 @@ import DOM.Node.Types (HTMLCollection(), Element(), Document(), ElementId(..),
import Data.Either (fromRight)
import Data.Foreign (toForeign)
import Data.Maybe (Maybe(), maybe, fromJust)
import Data.Nullable (toMaybe)
import Partial.Unsafe (unsafePartial)
import Control.Monad.Except (runExcept)

getDocument :: forall eff. Eff (dom :: DOM | eff) Document
getDocument = window >>= document <#> htmlDocumentToDocument
Expand All @@ -27,8 +27,7 @@ getElementById' :: forall eff. String
-> Eff (dom :: DOM | eff) (Maybe Element)
getElementById' id doc = do
let docNode = documentToNonElementParentNode doc
nullableEl <- getElementById (ElementId id) docNode
pure $ toMaybe nullableEl
getElementById (ElementId id) docNode

-- | Perform a DOM action with a single element which can be accessed by ID
withElementById :: forall eff. String
Expand All @@ -45,13 +44,13 @@ addEventListener' etype listener target =
addEventListener etype (eventListener listener) true target

unsafeElementToHTMLElement :: Element -> HTMLElement
unsafeElementToHTMLElement = unsafePartial (fromRight <<< readHTMLElement <<< toForeign)
unsafeElementToHTMLElement = unsafePartial (fromRight <<< runExcept <<< readHTMLElement <<< toForeign)

unsafeEventToKeyboardEvent :: Event -> KeyboardEvent
unsafeEventToKeyboardEvent = unsafePartial (fromRight <<< readKeyboardEvent <<< toForeign)
unsafeEventToKeyboardEvent = unsafePartial (fromRight <<< runExcept <<< readKeyboardEvent <<< toForeign)

unsafeGetAttribute :: forall eff. String -> Element -> Eff (dom :: DOM | eff) String
unsafeGetAttribute key el = unsafePartial (fromJust <<< toMaybe) <$> getAttribute key el
unsafeGetAttribute key el = unsafePartial fromJust <$> getAttribute key el

foreign import getSelectedValue :: forall eff. Element
-> Eff (dom :: DOM | eff) String
Expand Down
2 changes: 1 addition & 1 deletion src/Helper.purs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ import Types (Level, LevelId, Difficulty, Wall, Cube)

-- | Create a StrMap from an Array of (key, value) pairs
fromArray :: forall a. Array (Tuple String a) -> SM.StrMap a
fromArray = SM.fromList <<< fromFoldable
fromArray = SM.fromFoldable

-- | Operator to create tuples, especially for creating maps with
-- | `Map.fromList ["key1" :> "value1", "key2" :> "value2"]`
Expand Down
12 changes: 5 additions & 7 deletions src/Main.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@ module Main (App(..), main) where

import Prelude
import Color (rgb, graytone)
import Control.Bind ((=<<))
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (CONSOLE, log, logShow)
import DOM (DOM)
Expand All @@ -22,7 +21,6 @@ import Data.Int (toNumber)
import Data.List (List(..), fromFoldable, filter, snoc, dropWhile, tail, head, (:), last, mapMaybe, reverse, length)
import Data.Maybe (Maybe(..), fromMaybe, maybe, fromJust)
import Data.Monoid (class Monoid, mempty)
import Data.Nullable (toMaybe)
import Data.StrMap as SM
import Data.String.Regex (regex, parseFlags, replace)
import Data.Traversable (traverse)
Expand Down Expand Up @@ -57,7 +55,7 @@ spacing = 5.5

-- | Like `foldMap` on `List`, but the function also takes an index parameter
foldMapIndexed :: forall a m. (Monoid m) => (Int -> a -> m) -> List a -> m
foldMapIndexed f xs = go 0 xs
foldMapIndexed f xs' = go 0 xs'
where go _ Nil = mempty
go i (Cons x xs) = f i x <> go (i + 1) xs

Expand Down Expand Up @@ -144,7 +142,7 @@ render setupUI gs = do

-- On-canvas rendering
let lightPos = { x: -2.0, y: 1.0, z: 3.0 }
clearRect ctx { x: 0.0, y: 0.0, w, h }
_ <- clearRect ctx { x: 0.0, y: 0.0, w, h }

let renderCanvas x y s scene = D.render ctx $ D.translate x y $
renderScene lightPos (scale s scene)
Expand Down Expand Up @@ -180,8 +178,8 @@ replaceAll regexString replacement = replace pattern replacement

-- | Replace color placeholders in the transformer description by colored rectangular divs
replaceColors :: String -> String
replaceColors s =
foldl replaceColor s ("X" : map show (Cyan `enumFromTo` Yellow))
replaceColors s' =
foldl replaceColor s' ("X" : map show (Cyan `enumFromTo` Yellow))
where replaceColor s c = replaceAll (pattern c) (replacement c) s
pattern c = "{" <> c <> "}"
replacement c = "<div class=\"cube " <> c <> "\"> </div>"
Expand Down Expand Up @@ -253,7 +251,7 @@ keyPress event = void do
clickLi :: Element -> Event -> App
clickLi liEl event = do
newId <- unsafeGetAttribute "id" liEl
ul <- unsafeFromJust <$> toMaybe <$> parentElement (elementToNode liEl)
ul <- unsafeFromJust <$> parentElement (elementToNode liEl)
ulId <- unsafeGetAttribute "id" ul
modifyGameStateAndRender true (modify ulId newId)

Expand Down
4 changes: 2 additions & 2 deletions src/Storage.purs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
module Storage where

import Prelude
import Control.Monad.Eff (Eff)
import Control.Monad.Eff (kind Effect, Eff)
import Data.Array as A
import Data.List (fromFoldable)
import Data.Maybe (Maybe(..))
Expand All @@ -10,7 +10,7 @@ import Data.StrMap as SM

import Types (GameState, TransformerId, LevelId)

foreign import data STORAGE :: !
foreign import data STORAGE :: Effect

type SaveableGameState = {
currentLevel :: LevelId,
Expand Down

0 comments on commit b47d427

Please sign in to comment.