~sjm/builds-character

3710596ee5b6f32e6c1244237ee6308668f82de7 — Sam Marshall 3 years ago 313f103
feat: render level and allow xp to change
A readme.org => readme.org +6 -0
@@ 0,0 1,6 @@
* Builds Character

a Stars Without Number p2p Character Sheet.

** todo list
*** TODO save sheet on update

M scripts.org => scripts.org +5 -5
@@ 11,9 11,9 @@ $ /home/sam/Documents/code/builds-character/node_modules/.bin/parcel build ./ind
Building...
Bundling...
Packaging & Optimizing...
✨ Built in 9.08s
✨ Built in 7.40s

dist/index.17404c54.js                          622.92 KB    5.98s
dist/index.1b2e5459.js                          644.66 KB    6.28s
├── output/Data.Map.Internal/index.js            35.27 KB     45ms
├── output/Data.List/index.js                     17.4 KB     55ms
├── output/Data.List.Lazy/index.js               16.62 KB     57ms


@@ 24,11 24,11 @@ dist/index.17404c54.js                          622.92 KB    5.98s
├── output/Data.Array/index.js                   10.15 KB     47ms
├── output/Data.FoldableWithIndex/index.js        9.86 KB     44ms
└── output/Halogen.Query.HalogenM/index.js         8.8 KB    193ms
└── + 360 more assets
└── + 377 more assets

dist/index.html                                     152 B    148ms
dist/index.html                                     152 B    174ms
└── index.html                                      194 B     53ms
Done in 10.07s.
Done in 8.67s.
#+end_example

#+name: launch-project

M src/CharSheet.purs => src/CharSheet.purs +7 -1
@@ 1,4 1,4 @@
module CharSheet (Character(..), fresh, fromJson, write, xp) where
module CharSheet (Character(..), fresh, fromJson, write, xp, setXP, modifyXP) where

import Prelude



@@ 22,6 22,12 @@ fresh = Character { xp : XP.xp 0 }
xp :: Character -> XP.XP
xp (Character { xp: x }) = x

modifyXP :: (XP.XP -> XP.XP) -> Character -> Character
modifyXP f (Character c) = Character $ c { xp = ( f c.xp ) }

setXP :: Character -> XP.XP -> Character
setXP (Character c) x = Character $ c { xp = x }

fromJson :: A.Json -> Maybe Character
fromJson j = do
  x <- I.ceil <$> (L.preview (A._Object <<< ix "xp" <<< A._Number) j)

A src/CharSheet/Level.purs => src/CharSheet/Level.purs +8 -0
@@ 0,0 1,8 @@
module CharSheet.Level where

import Prelude

newtype Level = Level Int

instance showLevel :: Show Level where
  show (Level int) = "Level: " <> show int

M src/CharSheet/XP.purs => src/CharSheet/XP.purs +14 -8
@@ 1,15 1,13 @@
module CharSheet.XP (XP, Level, _xp, xp, level) where
module CharSheet.XP (XP, _xp, xp, toLevel, inc, dec) where

import Prelude

import CharSheet.Level (Level(..))

newtype XP = XP Int
newtype Level = Level Int

instance showXP :: Show XP where
  show (XP int) = show int

instance showLevel :: Show Level where
  show (Level int) = show int
  show (XP int) = "XP: " <> show int

_xp :: XP -> Int
_xp (XP i) = i


@@ 17,8 15,16 @@ _xp (XP i) = i
xp :: Int -> XP
xp = XP

level :: XP -> Level
level (XP count)
inc :: XP -> XP
inc (XP i) = XP (i + 1)

dec :: XP -> XP
dec (XP i)
  | i > 0 = XP (i - 1)
  | otherwise = XP i

toLevel :: XP -> Level
toLevel (XP count)
  | count < 3 = Level 1
  | count < 6 = Level 2
  | count < 12 = Level 3

M src/Main.purs => src/Main.purs +6 -1
@@ 4,6 4,7 @@ import Prelude

import Beaker.HyperDrive as BHD
import CharSheet as C
import Data.Maybe (Maybe(..))
import Effect (Effect)
import Effect.Aff (Aff, launchAff_)
import Effect.Class (liftEffect)


@@ 13,7 14,7 @@ import Halogen.Aff as HA
import Halogen.VDom.Driver (runUI)
import UI.Entry as Entry

entry :: forall q o. Aff (H.HalogenIO q o Aff)
entry :: forall o. Aff (H.HalogenIO Entry.Query o Aff)
entry = do
  body <- HA.awaitBody



@@ 25,4 26,8 @@ main = launchAff_ do
  ui <- entry
  json <- C.fromJson <$> BHD.readFileJSON "/data.json"

  _ <- case json of
    Just c -> ui.query $ H.mkTell $ Entry.Load c
    Nothing -> pure Nothing

  liftEffect $ Console.logShow "Done"

M src/UI/Entry.purs => src/UI/Entry.purs +36 -7
@@ 3,26 3,55 @@ module UI.Entry where
import Prelude

import CharSheet as C
import CharSheet.XP as CXP
import Data.Maybe (Maybe(..))
import Effect.Class (class MonadEffect)
import Halogen as H
import Halogen.HTML as HH
import Type.Proxy (Proxy(..))
import UI.Level as UILevel
import UI.XP as UIXP

type State = C.Character
type Input = C.Character

data Action = Update Input
data Query a = Load Input a

component :: forall q o m. H.Component q Input o m
data Action =
  XPOutput UIXP.Output

type Slots = ( xp :: UIXP.Slot
             , lvl :: (UILevel.Slot Unit)
             )

_xp = Proxy :: Proxy "xp"
_lvl = Proxy :: Proxy "lvl"

component :: forall m o. MonadEffect m => H.Component Query Input o m
component = H.mkComponent { initialState
                          , render
                          , eval : H.mkEval $ H.defaultEval { handleAction = handleAction }}
                          , eval : H.mkEval $ H.defaultEval { handleQuery = handleQuery
                                                            , handleAction = handleAction }}

initialState :: Input -> State
initialState = identity

render :: forall w i. State -> HH.HTML w i
render state = HH.div_ [ UIXP.component $ C.xp state ]
render :: forall m. MonadEffect m => State -> H.ComponentHTML Action Slots m
render state = let
  xp = C.xp state
  in
    HH.div_ [ HH.slot _xp 0 UIXP.component { xp } XPOutput
            , HH.slot_ _lvl unit UILevel.component xp ]

handleAction :: forall o m. Action -> H.HalogenM State Action () o m Unit
handleAction :: forall o m. MonadEffect m => Action -> H.HalogenM State Action Slots o m Unit
handleAction = case _ of
  Update c -> H.modify_ \_ -> c
  XPOutput output -> case output of
    UIXP.IncXP -> do
      H.modify_ $ C.modifyXP CXP.inc
    UIXP.DecXP -> H.modify_ $ C.modifyXP CXP.dec

handleQuery :: forall a m o. Query a -> H.HalogenM State Action Slots o m (Maybe a)
handleQuery = case _ of
  Load c a -> do
    H.modify_ \_ -> c
    pure (Just a)

A src/UI/Level.purs => src/UI/Level.purs +34 -0
@@ 0,0 1,34 @@
module UI.Level where

import Prelude

import CharSheet.XP as CX
import Data.Maybe (Maybe(..))
import Halogen as H
import Halogen.HTML as HH

type Input = CX.XP
type State = CX.XP

data Action = Update Input

type Slot s = forall q o. H.Slot q o s

component :: forall q o m. H.Component q Input o m
component = H.mkComponent { initialState
                          , render
                          , eval : H.mkEval $ H.defaultEval { handleAction = handleAction
                                                            , receive = Just <<< Update
                                                            }
                          }

initialState :: Input -> State
initialState = identity

render :: forall a m. State -> H.ComponentHTML a () m
render s = HH.div_ [ HH.text $ show $ CX.toLevel s ]

handleAction :: forall o m. Action -> H.HalogenM State Action () o m Unit
handleAction = case _ of
  Update xp -> do
    H.modify_ $ const xp

M src/UI/XP.purs => src/UI/XP.purs +38 -3
@@ 3,8 3,43 @@ module UI.XP where
import Prelude

import CharSheet.XP as CX
import Data.Maybe (Maybe(..))
import Effect.Class (class MonadEffect)
import Effect.Console as Console
import Halogen as H
import Halogen.HTML as HH
import Halogen.HTML.Events as HE

-- component to display XP
component :: forall w i. CX.XP -> HH.HTML w i
component xp = HH.p_ [ HH.text $ "XP: " <> show xp ]
type Input = { xp :: CX.XP }
type State = { xp :: CX.XP }

data Output = IncXP
            | DecXP

data Action = Inc | Dec | Update Input

type Slot = forall query. H.Slot query Output Int

component :: forall q m. MonadEffect m => H.Component q Input Output m
component = H.mkComponent { initialState
                          , render
                          , eval : H.mkEval $ H.defaultEval { handleAction = handleAction
                                                            , receive = Just <<< Update
                                                            }
                          }

initialState :: Input -> State
initialState = identity

render :: forall m. State -> H.ComponentHTML Action () m
render { xp } = HH.div_ [ HH.button [ HE.onClick \_ -> Inc  ] [ HH.text "+" ]
                        , HH.p_ [ HH.text $ show xp ]
                        , HH.button [ HE.onClick \_ -> Dec ] [ HH.text "-" ]
                        ]

handleAction :: forall m. MonadEffect m => Action -> H.HalogenM State Action () Output m Unit
handleAction = case _ of
  Inc -> H.raise IncXP
  Dec -> H.raise DecXP
  Update xp -> do
    H.modify_ $ const xp