about summary refs log tree commit diff
path: root/users/aspen/xanthous/src/Xanthous/Game/Prompt.hs
blob: 2d6c0a280f418e477a8bc54f6d2e0be85c21b96a (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
{-# LANGUAGE DeriveFunctor        #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE StandaloneDeriving   #-}
{-# LANGUAGE GADTs                #-}
--------------------------------------------------------------------------------
module Xanthous.Game.Prompt
  ( PromptType(..)
  , SPromptType(..)
  , SingPromptType(..)
  , PromptCancellable(..)
  , PromptResult(..)
  , PromptState(..)
  , promptStatePosition
  , MenuOption(..)
  , mkMenuItems
  , PromptInput
  , Prompt(..)
  , mkPrompt
  , mkStringPrompt
  , mkStringPromptWithDefault
  , mkMenu
  , mkPointOnMapPrompt
  , mkFirePrompt
  , isCancellable
  , submitPrompt
  ) where
--------------------------------------------------------------------------------
import           Xanthous.Prelude
--------------------------------------------------------------------------------
import           Brick.Widgets.Edit (Editor, editorText, getEditContents)
import           Test.QuickCheck
import           Test.QuickCheck.Arbitrary.Generic
--------------------------------------------------------------------------------
import           Xanthous.Util (smallestNotIn, AlphaChar (..))
import           Xanthous.Data (Direction, Position, Tiles)
import           Xanthous.Data.App (ResourceName)
import qualified Xanthous.Data.App as Resource
--------------------------------------------------------------------------------

data PromptType where
  StringPrompt    :: PromptType
  Confirm         :: PromptType
  Menu            :: Type -> PromptType
  DirectionPrompt :: PromptType
  PointOnMap      :: PromptType
  -- | Throw an item or fire a projectile weapon. Prompt is to select the
  -- direction
  Fire            :: PromptType
  Continue        :: PromptType
  deriving stock (Generic)

instance Show PromptType where
  show StringPrompt = "StringPrompt"
  show Confirm = "Confirm"
  show (Menu _) = "Menu"
  show DirectionPrompt = "DirectionPrompt"
  show PointOnMap = "PointOnMap"
  show Continue = "Continue"
  show Fire = "Fire"

data SPromptType :: PromptType -> Type where
  SStringPrompt    :: SPromptType 'StringPrompt
  SConfirm         :: SPromptType 'Confirm
  SMenu            :: SPromptType ('Menu a)
  SDirectionPrompt :: SPromptType 'DirectionPrompt
  SPointOnMap      :: SPromptType 'PointOnMap
  SContinue        :: SPromptType 'Continue
  SFire            :: SPromptType 'Fire

instance NFData (SPromptType pt) where
  rnf SStringPrompt = ()
  rnf SConfirm = ()
  rnf SMenu = ()
  rnf SDirectionPrompt = ()
  rnf SPointOnMap = ()
  rnf SContinue = ()
  rnf SFire = ()

class SingPromptType pt where singPromptType :: SPromptType pt
instance SingPromptType 'StringPrompt where singPromptType = SStringPrompt
instance SingPromptType 'Confirm where singPromptType = SConfirm
instance SingPromptType 'DirectionPrompt where singPromptType = SDirectionPrompt
instance SingPromptType 'PointOnMap where singPromptType = SPointOnMap
instance SingPromptType 'Continue where singPromptType = SContinue
instance SingPromptType 'Fire where singPromptType = SFire

instance Show (SPromptType pt) where
  show SStringPrompt    = "SStringPrompt"
  show SConfirm         = "SConfirm"
  show SMenu            = "SMenu"
  show SDirectionPrompt = "SDirectionPrompt"
  show SPointOnMap      = "SPointOnMap"
  show SContinue        = "SContinue"
  show SFire            = "SFire"

data PromptCancellable
  = Cancellable
  | Uncancellable
  deriving stock (Show, Eq, Ord, Enum, Generic)
  deriving anyclass (NFData, CoArbitrary, Function)

instance Arbitrary PromptCancellable where
  arbitrary = genericArbitrary

data PromptResult (pt :: PromptType) where
  StringResult     :: Text      -> PromptResult 'StringPrompt
  ConfirmResult    :: Bool      -> PromptResult 'Confirm
  MenuResult       :: forall a. a    -> PromptResult ('Menu a)
  DirectionResult  :: Direction -> PromptResult 'DirectionPrompt
  PointOnMapResult :: Position  -> PromptResult 'PointOnMap
  FireResult       :: Position  -> PromptResult 'Fire
  ContinueResult   ::             PromptResult 'Continue

instance Arbitrary (PromptResult 'StringPrompt) where
  arbitrary = StringResult <$> arbitrary

instance Arbitrary (PromptResult 'Confirm) where
  arbitrary = ConfirmResult <$> arbitrary

instance Arbitrary a => Arbitrary (PromptResult ('Menu a)) where
  arbitrary = MenuResult <$> arbitrary

instance Arbitrary (PromptResult 'DirectionPrompt) where
  arbitrary = DirectionResult <$> arbitrary

instance Arbitrary (PromptResult 'PointOnMap) where
  arbitrary = PointOnMapResult <$> arbitrary

instance Arbitrary (PromptResult 'Continue) where
  arbitrary = pure ContinueResult

instance Arbitrary (PromptResult 'Fire) where
  arbitrary = FireResult <$> arbitrary

--------------------------------------------------------------------------------

data PromptState pt where
  StringPromptState
    :: Editor Text ResourceName     -> PromptState 'StringPrompt
  DirectionPromptState  ::            PromptState 'DirectionPrompt
  ContinuePromptState   ::            PromptState 'Continue
  ConfirmPromptState    ::            PromptState 'Confirm
  MenuPromptState       :: forall a.       PromptState ('Menu a)
  PointOnMapPromptState :: Position -> PromptState 'PointOnMap
  FirePromptState       :: Position -> PromptState 'Fire

instance NFData (PromptState pt) where
  rnf sps@(StringPromptState ed) = sps `deepseq` ed `deepseq` ()
  rnf DirectionPromptState = ()
  rnf ContinuePromptState = ()
  rnf ConfirmPromptState = ()
  rnf MenuPromptState = ()
  rnf pomps@(PointOnMapPromptState pos) = pomps `deepseq` pos `deepseq` ()
  rnf fps@(FirePromptState pos) = fps `deepseq` pos `deepseq` ()

instance Arbitrary (PromptState 'StringPrompt) where
  arbitrary = StringPromptState <$> arbitrary

instance Arbitrary (PromptState 'DirectionPrompt) where
  arbitrary = pure DirectionPromptState

instance Arbitrary (PromptState 'Continue) where
  arbitrary = pure ContinuePromptState

instance Arbitrary (PromptState ('Menu a)) where
  arbitrary = pure MenuPromptState

instance Arbitrary (PromptState 'Fire) where
  arbitrary = FirePromptState <$> arbitrary

instance CoArbitrary (PromptState 'StringPrompt) where
  coarbitrary (StringPromptState ed) = coarbitrary ed

instance CoArbitrary (PromptState 'DirectionPrompt) where
  coarbitrary DirectionPromptState = coarbitrary ()

instance CoArbitrary (PromptState 'Continue) where
  coarbitrary ContinuePromptState = coarbitrary ()

instance CoArbitrary (PromptState ('Menu a)) where
  coarbitrary MenuPromptState = coarbitrary ()

instance CoArbitrary (PromptState 'Fire) where
  coarbitrary (FirePromptState pos) = coarbitrary pos

deriving stock instance Show (PromptState pt)

-- | Traversal over the position for the prompt types with positions in their
-- prompt state (currently 'Fire' and 'PointOnMap')
promptStatePosition :: forall pt. Traversal' (PromptState pt) Position
promptStatePosition _ ps@(StringPromptState _) = pure ps
promptStatePosition _ DirectionPromptState = pure DirectionPromptState
promptStatePosition _ ContinuePromptState = pure ContinuePromptState
promptStatePosition _ ConfirmPromptState = pure ConfirmPromptState
promptStatePosition _ MenuPromptState = pure MenuPromptState
promptStatePosition f (PointOnMapPromptState p) = PointOnMapPromptState <$> f p
promptStatePosition f (FirePromptState p) = FirePromptState <$> f p

data MenuOption a = MenuOption Text a
  deriving stock (Eq, Generic, Functor)
  deriving anyclass (NFData, CoArbitrary, Function)

instance Comonad MenuOption where
  extract (MenuOption _ x) = x
  extend cok mo@(MenuOption text _) = MenuOption text (cok mo)

mkMenuItems :: (MonoFoldable f, Element f ~ (Char, MenuOption a))
            => f
            -> Map Char (MenuOption a)
mkMenuItems = flip foldl' mempty $ \items (chr, option) ->
  let chr' = if has (ix chr) items
             then getAlphaChar . smallestNotIn . map AlphaChar $ keys items
             else chr
  in items & at chr' ?~ option

instance Show (MenuOption a) where
  show (MenuOption m _) = show m

type family PromptInput (pt :: PromptType) :: Type where
  PromptInput ('Menu a)     = Map Char (MenuOption a)
  PromptInput 'PointOnMap   = Position -- Character pos
  PromptInput 'Fire         = (Position, Tiles) -- Nearest enemy, range
  PromptInput 'StringPrompt = Maybe Text -- Default value
  PromptInput _ = ()

data Prompt (m :: Type -> Type) where
  Prompt
    :: forall (pt :: PromptType)
        (m :: Type -> Type).
      PromptCancellable
    -> SPromptType pt
    -> PromptState pt
    -> PromptInput pt
    -> (PromptResult pt -> m ())
    -> Prompt m

instance Show (Prompt m) where
  show (Prompt c pt ps pri _)
    = "(Prompt "
    <> show c <> " "
    <> show pt <> " "
    <> show ps <> " "
    <> showPri
    <> " <function>)"
    where showPri = case pt of
            SMenu -> show pri
            _ -> "()"

instance NFData (Prompt m) where
  rnf (Prompt c SMenu ps pri cb)
            = c
    `deepseq` ps
    `deepseq` pri
    `seq` cb
    `seq` ()
  rnf (Prompt c spt ps pri cb)
            = c
    `deepseq` spt
    `deepseq` ps
    `deepseq` pri
    `seq` cb
    `seq` ()

instance CoArbitrary (m ()) => CoArbitrary (Prompt m) where
  coarbitrary (Prompt c SStringPrompt ps pri cb) =
    variant @Int 1 . coarbitrary (c, ps, pri, cb)
  coarbitrary (Prompt c SConfirm _ pri cb) = -- TODO fill in prompt state
    variant @Int 2 . coarbitrary (c, pri, cb)
  coarbitrary (Prompt c SMenu _ps _pri _cb) =
    variant @Int 3 . coarbitrary c {-, ps, pri, cb -}
  coarbitrary (Prompt c SDirectionPrompt ps pri cb) =
    variant @Int 4 . coarbitrary (c, ps, pri, cb)
  coarbitrary (Prompt c SPointOnMap _ pri cb) = -- TODO fill in prompt state
    variant @Int 5 . coarbitrary (c, pri, cb)
  coarbitrary (Prompt c SContinue ps pri cb) =
    variant @Int 6 . coarbitrary (c, ps, pri, cb)
  coarbitrary (Prompt c SFire ps pri cb) =
    variant @Int 7 . coarbitrary (c, ps, pri, cb)

-- instance Function (Prompt m) where
--   function = functionMap toTuple _fromTuple
--     where
--       toTuple (Prompt c pt ps pri cb) = (c, pt, ps, pri, cb)


mkPrompt
  :: (PromptInput pt ~ ())
  => PromptCancellable       -- ^ Is the prompt cancellable or not?
  -> SPromptType pt          -- ^ The type of the prompt
  -> (PromptResult pt -> m ()) -- ^ Function to call when the prompt is complete
  -> Prompt m
mkPrompt c pt@SDirectionPrompt cb = Prompt c pt DirectionPromptState () cb
mkPrompt c pt@SContinue cb = Prompt c pt ContinuePromptState () cb
mkPrompt c pt@SConfirm cb = Prompt c pt ConfirmPromptState () cb

mkStringPrompt
  :: PromptCancellable                  -- ^ Is the prompt cancellable or not?
  -> (PromptResult 'StringPrompt -> m ()) -- ^ Function to call when the prompt is complete
  -> Prompt m
mkStringPrompt c =
  let ps = StringPromptState $ editorText Resource.Prompt (Just 1) ""
  in Prompt c SStringPrompt ps Nothing

mkStringPromptWithDefault
  :: PromptCancellable                  -- ^ Is the prompt cancellable or not?
  -> Text                               -- ^ Default value for the prompt
  -> (PromptResult 'StringPrompt -> m ()) -- ^ Function to call when the prompt is complete
  -> Prompt m
mkStringPromptWithDefault c def =
  let ps = StringPromptState $ editorText Resource.Prompt (Just 1) ""
  in Prompt c SStringPrompt ps (Just def)

mkMenu
  :: forall a m.
    PromptCancellable
  -> Map Char (MenuOption a) -- ^ Menu items
  -> (PromptResult ('Menu a) -> m ())
  -> Prompt m
mkMenu c = Prompt c SMenu MenuPromptState

mkPointOnMapPrompt
  :: PromptCancellable
  -> Position
  -> (PromptResult 'PointOnMap -> m ())
  -> Prompt m
mkPointOnMapPrompt c pos = Prompt c SPointOnMap (PointOnMapPromptState pos) pos

mkFirePrompt
  :: PromptCancellable
  -> Position -- ^ Initial position
  -> Tiles    -- ^ Range
  -> (PromptResult 'Fire -> m ())
  -> Prompt m
mkFirePrompt c pos range = Prompt c SFire (FirePromptState pos) (pos, range)

isCancellable :: Prompt m -> Bool
isCancellable (Prompt Cancellable _ _ _ _)   = True
isCancellable (Prompt Uncancellable _ _ _ _) = False

submitPrompt :: Applicative m => Prompt m -> m ()
submitPrompt (Prompt _ pt ps pri cb) =
  case (pt, ps, pri) of
    (SStringPrompt, StringPromptState edit, mDef) ->
      let inputVal = mconcat . getEditContents $ edit
          val | null inputVal, Just def <- mDef = def
              | otherwise = inputVal
      in cb $ StringResult val
    (SDirectionPrompt, DirectionPromptState, _) ->
      pure () -- Don't use submit with a direction prompt
    (SContinue, ContinuePromptState, _) ->
      cb ContinueResult
    (SMenu, MenuPromptState, _) ->
      pure () -- Don't use submit with a menu prompt
    (SPointOnMap, PointOnMapPromptState pos, _) ->
      cb $ PointOnMapResult pos
    (SConfirm, ConfirmPromptState, _) ->
      cb $ ConfirmResult True
    (SFire, FirePromptState pos, _) ->
      cb $ FireResult pos