#!/usr/bin/env stack {- stack script --resolver lts-19.23 --install-ghc -} {-# OPTIONS_GHC -Wall -Wno-unused-imports -Wno-unused-top-binds -Wno-name-shadowing #-} {-# language NoImplicitPrelude #-} {-# language RecordWildCards #-} {-# language FlexibleContexts #-} {-# language TemplateHaskell #-} {-# language ViewPatterns #-} {-# language OverloadedStrings #-} {-# language DeriveGeneric #-} {-# language DerivingVia #-} {-# language TupleSections #-} import Rebase.Prelude hiding (toList, on, (<+>), Max) import qualified Rebase.Prelude as Prelude import qualified Data.Set as Set import qualified Data.Sequence as Seq import qualified Data.Sequence.NonEmpty as NESeq import Data.Sequence (Seq(..)) import Data.Sequence.NonEmpty (NESeq(..)) import Control.Lens hiding ((<|)) import Data.Foldable (toList) import Data.Ratio import Text.Printf import Graphics.Vty import Data.Time.LocalTime import Control.Monad.RWS import Data.Time.Calendar.OrdinalDate import qualified Data.Text as Text import Data.Text.Format.Numbers import Rebase.Data.Map.Strict (Map) import qualified Rebase.Data.Map.Strict as Map import Brick import Brick.Types import Data.Text (unpack) import Control.Lens import Control.Monad (void, forever) import Control.Concurrent (threadDelay, forkIO) import qualified Graphics.Vty as V import Brick.Widgets.ProgressBar as P import Brick.BChan import Brick.Widgets.Center import Brick.Widgets.Border import Brick.Main ( App(..) , showFirstCursor , customMain , continue , halt ) import qualified Brick.Main as M import Brick.AttrMap ( attrMap ) import Brick.Types ( Widget , Next , EventM , BrickEvent(..) ) import Brick.Widgets.Core ( (<=>) , str ) import Brick.AttrMap as A import Brick.Util (fg, bg, on, clamp) import Brick.Widgets.Core import Brick.Widgets.Table import Text.Pretty.Simple (pPrint) import GHC.Generics (Generic) import Generic.Data import Generic.Data.Microsurgery data Performance = Achieved { achievedReps :: Integer, achievedWeight :: Integer } deriving Generic deriving (Read, Show) via Surgery Derecordify Performance data LiftRecord = LiftRecord { liftName :: Text, stats :: [Performance] } deriving Generic deriving (Read, Show) via Surgery Derecordify LiftRecord -- "I highly recommend having a goal in mind for these last sets. Sit down the -- night before, or the week before, and think of the number of reps you’d like -- to hit. See yourself doing it. Write it down and visualize the bar in your -- hands or on your back. When it’s time, let yourself go and attack the -- weight." computeRepGoal :: Integer -> [Performance] -> (Integer) computeRepGoal targetWeight stats = head $ filter isPR [2..] where isPR n = computeOneRepMax (Achieved n targetWeight) > computeOneRepMax (bestPerformance stats) bestPerformance :: [Performance] -> Performance bestPerformance = head . sortBy (flip $ comparing computeOneRepMax) -- The formula from Jim Wendler's 5-3-1: -- 1RM = Weight x Reps x 0.0333 + Weight. computeOneRepMax :: Performance -> Rational computeOneRepMax Achieved{..} = toRational achievedWeight * (realToFrac achievedReps * 0.0333 + 1) showRational :: Rational -> String showRational n = printf format $ (realToFrac :: Rational -> Float) $ n where format = if floor (n * 10) `mod` 10 == (0 :: Integer) then "%.0f" else "%.2f" data WeekSelection = Week1 | Week2 | Week3 deriving (Enum, Bounded, Show, Eq) -- TODO: State contains chosen repmax formula -- TODO: State contains performances data St = St { _lifts :: [LiftRecord], _week :: WeekSelection, _sessions :: NESeq (Set Text), _selectedSession :: Int } makeLenses ''St -- TODO: Event for inotify on edited text file (as input interface) data CustomEvent = CustomEvent data SetScheme = SetScheme { ratioMax :: Rational, numberOfReps :: Integer, amrap :: Bool } setScheme, setSchemeAMRAP :: Rational -> Integer -> SetScheme setScheme percentage reps = SetScheme (percentage / 100) reps False setSchemeAMRAP percentage reps = SetScheme (percentage / 100) reps True data SetOption = Fresher | Heavier warmup :: [SetScheme] warmup = [setScheme 40 5, setScheme 50 5, setScheme 60 3] downSets :: [SetScheme] downSets = take 5 $ repeat $ setScheme 75 5 liftScheme :: SetOption -> WeekSelection -> [SetScheme] liftScheme Fresher Week1 = warmup ++ [setScheme 65 5, setScheme 75 5, setSchemeAMRAP 85 5] ++ downSets liftScheme Heavier Week1 = warmup ++ [setScheme 75 5, setScheme 80 5, setSchemeAMRAP 85 5] ++ downSets liftScheme Fresher Week2 = warmup ++ [setScheme 70 3, setScheme 80 3, setSchemeAMRAP 90 3] ++ downSets liftScheme Heavier Week2 = warmup ++ [setScheme 80 3, setScheme 85 3, setSchemeAMRAP 90 3] ++ downSets liftScheme _______ Week3 = warmup ++ [setScheme 75 5, setScheme 85 3, setSchemeAMRAP 95 1] ++ downSets data ListPosition = FirstInList | NotFirstInList deriving (Eq) annotatePosition :: [a] -> [(ListPosition, a)] annotatePosition [] = undefined annotatePosition (x:xs) = (FirstInList, x) : map (NotFirstInList,) xs lookup' :: Int -> NESeq a -> a lookup' i seq = fromJust $ NESeq.lookup (i `mod` NESeq.length seq) seq drawUI :: St -> [Widget ()] drawUI st = [vCenter $ vBox [hCenter oneRepMaxTable, header, withVScrollBarHandles $ withVScrollBars OnRight $ viewport () Vertical $ hCenter lastSetTable]] where lifts' = filter ((flip Set.member $ view sessions st & lookup' (view selectedSession st)) . liftName) (view lifts st) lastSetTable = renderTable $ table $ map (padLeftRight 1 . str) ["Lift", "Set", "Goal", "Done", "Rest"] : concatMap (toLiftRows (view week st)) lifts' header = str $ "Week " ++ case (view week st) of Week1 -> "1"; Week2 -> "2"; Week3 -> "3" oneRepMaxTable = renderTable $ table $ map (padLeftRight 1 . str) ["Lift", "Achieved Best", "Computed 1RM"] : map toRow lifts' toRow LiftRecord{..} = let best@Achieved{..} = bestPerformance stats in map (padLeftRight 2) [ txt $ liftName, str $ printf "%d @ %d" achievedReps achievedWeight, str $ showRational $ computeOneRepMax best ] toLiftRows :: WeekSelection -> LiftRecord -> [[Widget n]] toLiftRows week lift = (flip map) (annotatePosition $ liftScheme Fresher week) $ toLiftRow lift toLiftRow :: LiftRecord -> (ListPosition, SetScheme) -> [Widget n] toLiftRow LiftRecord{..} (position, (SetScheme targetRatio targetReps amrap)) = let best = bestPerformance stats computedTarget = targetRatio * (90 % 100) * computeOneRepMax best targetWeight = ceilingN 5 computedTarget repGoal = computeRepGoal targetWeight stats goalTo1RM g = computeOneRepMax $ Achieved g targetWeight showGoal g = printf "%2d @ %d ≈ 1 @ %s" g targetWeight (showRational (goalTo1RM g)) in map (padLeftRight 2) [ -- txt $ if position == FirstInList then liftName else " ", txt $ case position of FirstInList -> liftName; NotFirstInList -> if amrap then " \n " else " ", str $ printf "%2d%s @ %d%s" targetReps (if amrap then "+" else "" :: Text) targetWeight (if amrap then "\n " else "" :: String), str $ if amrap then showGoal repGoal ++ "\n" ++ showGoal (repGoal + 1) else " ", txt $ if amrap then " \n " else " ", txt $ if amrap then " \n " else " " ] ceilingN :: Integer -> Rational -> Integer ceilingN n x = ceiling (x / toRational n) * n succ' :: (Enum a, Bounded a, Eq a) => a -> a succ' x | x == maxBound = minBound succ' x = succ x clipSelectedSession :: St -> St clipSelectedSession st = st & selectedSession %~ maybeReset where len = view (sessions . to NESeq.length) st maybeReset n | n < 0 = len maybeReset n | n < len = n maybeReset _ | otherwise = 0 handleEvent :: St -> BrickEvent () CustomEvent -> EventM () (Next St) handleEvent st e = case e of VtyEvent (V.EvKey V.KEsc []) -> halt st VtyEvent (V.EvKey V.KDown _) -> M.vScrollBy (M.viewportScroll ()) 5 >> continue st VtyEvent (V.EvKey V.KUp _) -> M.vScrollBy (M.viewportScroll ()) (-5) >> continue st VtyEvent (V.EvKey (V.KChar 'w') _) -> continue $ st & week %~ succ' VtyEvent (V.EvKey (V.KChar 'n') _) -> continue $ st & selectedSession %~ (+1) & clipSelectedSession VtyEvent (V.EvKey (V.KChar 'p') _) -> continue $ st & selectedSession %~ (subtract 1) & clipSelectedSession VtyEvent _ -> continue st AppEvent _ -> continue st _ -> continue st theApp :: App St CustomEvent () theApp = App { appDraw = drawUI , appChooseCursor = showFirstCursor , appHandleEvent = handleEvent , appStartEvent = return , appAttrMap = const $ A.attrMap V.defAttr [] } -- Lift Ratios -- from https://www.catalystathletics.com/article/1786/The-Relation-of-Snatch-Clean-Jerk-and-Squat-Weights/ squat, deadlift, press :: Rational squat = 345 deadlift = 453 press = 140 cleanAndJerk = squat * 80 / 100 frontSquat = squat * 85 / 100 overheadSquat = squat * 65 / 100 snatch = squat * 60 / 100 powerSnatch = snatch * 80 / 100 clean = deadlift * 70 / 100 powerClean = clean * 80 / 100 pushPress = press * 100 / 75 jerk = pushPress / 100 * 85 routine :: NESeq (Set Text) routine = Set.fromList ["Deadlift", "Press"] :<|| Seq.fromList [ Set.fromList ["Front Squat"] , Set.fromList ["Left-Arm Snatch", "Right-Arm Snatch"] , Set.fromList ["Squat", "Bench"] , Set.fromList ["Push Press", "Power Clean"] ] main :: IO () main = do let buildVty = V.mkVty V.defaultConfig vty <- buildVty -- liftIO $ setMode (outputIface vty) Mouse True chan <- newBChan 10 initial <- read <$> readFile "lifts.dat" :: IO [LiftRecord] void $ customMain vty buildVty (Just chan) (theApp) (St initial Week1 routine 0)