~sjm/builds-character

c33ffb3d1fd43446f30ef8195df0a1c6f7486c99 — Sam Marshall 2 years ago 108b115
feat: add ui to set attributes manually.
4 files changed, 97 insertions(+), 42 deletions(-)

M readme.org
M src/UI/Attributes.purs
A src/UI/Attributes/Attribute.purs
M src/UI/Entry.purs
M readme.org => readme.org +7 -5
@@ 35,6 35,8 @@ relies on attributes and level

I won't be automating the setting of skills based on these, so that should also be explained somewhere.

This is basically gonna be a big old list.

**** Model Skills

Only show psychic skills for psychics.


@@ 49,12 51,7 @@ Weapons have damage dice and stuff, armour has armour class.

**** Model Name
**** Model Goal
**** Set Attributes Manually
*** Doing
**** Model Attribute Modifiers
These are derived solely from the Attributes, so can be read-only
***** Data
***** UI
*** Done
**** DONE save sheet on update
:LOGBOOK:


@@ 110,3 107,8 @@ wondering if I can use Halogen.Hooks for this one, as a little adventure. We'll 

****** Roll
****** Set Manually
**** Model Attribute Modifiers
These are derived solely from the Attributes, so can be read-only
***** Data
***** UI
**** Set Attributes Manually

M src/UI/Attributes.purs => src/UI/Attributes.purs +38 -35
@@ 1,14 1,16 @@
module UI.Attributes where

import Prelude

import CharSheet.Attributes as CA
import Data.Lens as L
import Data.Tuple.Nested ((/\))
import Effect.Class (class MonadEffect, liftEffect)
import Halogen as H
import Halogen.HTML as HH
import Halogen.HTML.Events as HE
import Halogen.Hooks as Hooks
import Type.Proxy (Proxy(..))
import UI.Attributes.Attribute as UAA
import UI.Util as Util

type Input


@@ 20,53 22,54 @@ data Message
type Slot s
  = forall q. H.Slot q Message s

attribute :: forall w i. String -> Int -> HH.HTML w i
attribute label attr =
  HH.div
    [ Util.classes [ "w-32", "h-8", "border-black", "border-2", "border-b-0", "grid", "grid-cols-3", "items-center" ] ]
    [ HH.div
        [ Util.classes [ "pr-2", "border-r-2", "border-black", "block", "text-right" ] ]
        [ HH.text label ]
    , HH.div [ Util.classes [ "block", "pr-2", "text-gray-400", "text-right" ] ] [ HH.text $ show attr ]
    , HH.div [ Util.classes [ "pr-2", "border-l-2", "border-black", "text-right" ] ] [ HH.text $ show (CA.modifier attr) ]
    ]
_attribute = Proxy :: Proxy "attribute"

str :: forall w i. Int -> HH.HTML w i
str = attribute "str"
component :: forall q m. MonadEffect m => H.Component q Input Message m
component =
  Hooks.component \tokens i -> Hooks.do
    let

dex :: forall w i. Int -> HH.HTML w i
dex = attribute "dex"
      incAttribute attr = (UpdateAttributes (L.over attr (_ + 1) i))
      decAttribute attr = (UpdateAttributes (L.over attr (_ - 1) i))

con :: forall w i. Int -> HH.HTML w i
con = attribute "con"
      handleStr = case _ of
        UAA.Increment -> Hooks.raise tokens.outputToken $ incAttribute CA._str
        UAA.Decrement -> Hooks.raise tokens.outputToken $ decAttribute CA._str

int :: forall w i. Int -> HH.HTML w i
int = attribute "int"
      handleDex = case _ of
        UAA.Increment -> Hooks.raise tokens.outputToken $ incAttribute CA._dex
        UAA.Decrement -> Hooks.raise tokens.outputToken $ decAttribute CA._dex

wis :: forall w i. Int -> HH.HTML w i
wis = attribute "wis"
      handleCon = case _ of
        UAA.Increment -> Hooks.raise tokens.outputToken $ incAttribute CA._con
        UAA.Decrement -> Hooks.raise tokens.outputToken $ decAttribute CA._con

cha :: forall w i. Int -> HH.HTML w i
cha = attribute "cha"
      handleInt = case _ of
        UAA.Increment -> Hooks.raise tokens.outputToken $ incAttribute CA._int
        UAA.Decrement -> Hooks.raise tokens.outputToken $ decAttribute CA._int

      handleWis = case _ of
        UAA.Increment -> Hooks.raise tokens.outputToken $ incAttribute CA._wis
        UAA.Decrement -> Hooks.raise tokens.outputToken $ decAttribute CA._wis

      handleCha = case _ of
        UAA.Increment -> Hooks.raise tokens.outputToken $ incAttribute CA._cha
        UAA.Decrement -> Hooks.raise tokens.outputToken $ decAttribute CA._cha

component :: forall q m. MonadEffect m => H.Component q Input Message m
component =
  Hooks.component \tokens i -> Hooks.do
    x /\ xID <- Hooks.useState 0
    let
      handleClick = do
        new <- liftEffect $ CA.fresh
        Hooks.raise tokens.outputToken (UpdateAttributes new)

    Hooks.pure do
      HH.div
        [ Util.classes [ "border-b-2", "border-black", "w-32", "mt-2" ] ]
        [ str (L.view CA._str i)
        , dex (L.view CA._dex i)
        , con (L.view CA._con i)
        , int (L.view CA._int i)
        , wis (L.view CA._wis i)
        , cha (L.view CA._cha i)
        , if CA.isEmpty i then
        [ HH.slot _attribute 0 UAA.component { label: "str", attribute: L.view CA._str i } handleStr
        , HH.slot _attribute 1 UAA.component { label: "dex", attribute: L.view CA._dex i } handleDex
        , HH.slot _attribute 2 UAA.component { label: "con", attribute: L.view CA._con i } handleCon
        , HH.slot _attribute 3 UAA.component { label: "int", attribute: L.view CA._int i } handleInt
        , HH.slot _attribute 4 UAA.component { label: "wis", attribute: L.view CA._wis i } handleWis
        , HH.slot _attribute 5 UAA.component { label: "cha", attribute: L.view CA._cha i } handleCha
                , if CA.isEmpty i then
            HH.button [ HE.onClick \_ -> handleClick ] [ HH.text "Roll" ]
          else
            HH.div_ []

A src/UI/Attributes/Attribute.purs => src/UI/Attributes/Attribute.purs +49 -0
@@ 0,0 1,49 @@
module UI.Attributes.Attribute where

import Prelude

import CharSheet.Attributes as CA
import Halogen as H
import Halogen.HTML as HH
import Halogen.HTML.Events as HE
import Halogen.Hooks as Hooks
import UI.Util as Util

type Input = { label :: String
             , attribute :: Int
             }

data Message
  = Increment
  | Decrement

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

component :: forall q m. H.Component q Input Message m
component = Hooks.component \tokens { label, attribute } -> Hooks.do
  let
    handleInc = do
      Hooks.raise tokens.outputToken (Increment)
    handleDec = do
      Hooks.raise tokens.outputToken (Decrement)

  Hooks.pure do
    HH.div
      [ Util.classes [ "w-40", "h-10", "border-black", "border-2", "border-b-0", "grid", "grid-cols-4", "items-center" ] ]
      [ HH.div
        [ Util.classes [ "pr-2", "border-r-2", "border-black", "block", "text-right" ] ]
        [ HH.text label ]
      , HH.div [ Util.classes [ "block", "pr-2", "text-gray-400", "text-right" ] ] [ HH.text $ show attribute ]
      , HH.div [ Util.classes [ "pr-2", "border-l-2", "border-black", "text-right" ] ] [ HH.text $ show (CA.modifier attribute) ]
      , HH.div
        [ Util.classes [ "grid", "grid-rows-2" ] ]
        [ HH.button
          [ Util.classes [ "w-4", "h-4", "border-black", "border", "flex", "justify-center", "items-center" ]
          , HE.onClick \_ -> handleInc ]
          [ HH.text "+" ]
        , HH.button
          [ Util.classes [ "w-4", "h-4", "border-black", "border", "flex", "justify-center", "items-center" ]
          , HE.onClick \_ -> handleDec]
          [ HH.text "-" ]
        ]
      ]

M src/UI/Entry.purs => src/UI/Entry.purs +3 -2
@@ 77,12 77,13 @@ render state =
          [ "border-solid"
          , "border-2"
          , "border-black"
          , "m-2"
          , "p-2"
          , "w-4/6"
          ]
      ]
      [ HH.slot _class unit UC.component cl ChangeClass
      , HH.slot _xp unit UIXP.component { xp } XPOutput
      , HH.slot_ _lvl unit UILevel.component xp
      , HH.div [ Util.classes [ "grid", "grid-cols-2", "w-1/2" ] ] [ HH.slot _xp unit UIXP.component { xp } XPOutput, HH.slot_ _lvl unit UILevel.component xp ]
      , HH.slot _attributes unit UA.component attr ChangeAttributes
      ]