Add feedback and a hasklet.
This commit is contained in:
		
							parent
							
								
									f21332c647
								
							
						
					
					
						commit
						a954b9ba02
					
				
							
								
								
									
										201
									
								
								Hasklet4.hs
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										201
									
								
								Hasklet4.hs
									
									
									
									
									
										Normal file
									
								
							@ -0,0 +1,201 @@
 | 
				
			|||||||
 | 
					{-# LANGUAGE TupleSections #-}
 | 
				
			||||||
 | 
					module Hasklet4 where
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					import Control.Monad
 | 
				
			||||||
 | 
					import Data.Bifunctor
 | 
				
			||||||
 | 
					import Data.Bool
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- * Stack language syntax
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Stack programs.
 | 
				
			||||||
 | 
					type Prog = [Cmd]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Commands for working with stacks of integers. 0 is treated as 'false',
 | 
				
			||||||
 | 
					--   all other values as 'true'. The examples below help illustrate the
 | 
				
			||||||
 | 
					--   behavior of some of the less obvious commands.
 | 
				
			||||||
 | 
					data Cmd
 | 
				
			||||||
 | 
					   = Push Int      -- ^ push an integer onto the stack
 | 
				
			||||||
 | 
					   | Drop          -- ^ drop the top element on the stack
 | 
				
			||||||
 | 
					   | Dig           -- ^ moves the ith element down to the top of the stack
 | 
				
			||||||
 | 
					   | Dup           -- ^ duplicate the top element on the stack
 | 
				
			||||||
 | 
					   | Neg           -- ^ negate the number on top of the stack
 | 
				
			||||||
 | 
					   | Add           -- ^ add the top two numbers on the stack
 | 
				
			||||||
 | 
					   | Mul           -- ^ multiply the top two numbers on the stack
 | 
				
			||||||
 | 
					   | LEq           -- ^ check whether the top element is less-than-or-equal to the second
 | 
				
			||||||
 | 
					   | If Prog Prog  -- ^ if the value on top is true, run the first program, else the second (consumes the test element)
 | 
				
			||||||
 | 
					   | While Prog    -- ^ loop as long as the top element is true (does not consume the test element)
 | 
				
			||||||
 | 
					  deriving (Eq,Show)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- ** Example programs and expected results
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- Note that the expected results are written with the top element of the
 | 
				
			||||||
 | 
					-- stack on the *right*, which is the convention for stack-based languages.
 | 
				
			||||||
 | 
					-- However, since we're encoding stacks with Haskell lists, the resulting
 | 
				
			||||||
 | 
					-- Haskell values will be in the reverse order.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Result: 4 5 5
 | 
				
			||||||
 | 
					p1 = [Push 4, Push 5, Push 6, Drop, Dup]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Result: 10 11 13 14 12
 | 
				
			||||||
 | 
					p2 = [Push 10, Push 11, Push 12, Push 13, Push 14, Push 3, Dig]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Result: 27 -5
 | 
				
			||||||
 | 
					p3 = [Push 3, Push 4, Push 5, Add, Mul, Push 5, Neg]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Result: 0 1
 | 
				
			||||||
 | 
					p4 = [Push 3, Push 4, LEq, Push 4, Push 3, LEq]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Result: 22
 | 
				
			||||||
 | 
					p5 = [Push 2, Push 3, Push 4, LEq, If [Push 10, Add] [Push 20, Add]]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Compute the factorial of the top element of the stack.
 | 
				
			||||||
 | 
					fac = [
 | 
				
			||||||
 | 
					  Push 1,             -- acc = 1
 | 
				
			||||||
 | 
					  Push 2, Dig,        -- move i to top
 | 
				
			||||||
 | 
					  While [             -- while i /= 0
 | 
				
			||||||
 | 
					    Dup,              --   duplicate i
 | 
				
			||||||
 | 
					    Push 3, Dig,      --   move accumulator to top
 | 
				
			||||||
 | 
					    Mul,              --   acc * i
 | 
				
			||||||
 | 
					    Push 2, Dig,      --   move i back to top
 | 
				
			||||||
 | 
					    Push 1, Neg, Add  --   decrement i
 | 
				
			||||||
 | 
					    ],
 | 
				
			||||||
 | 
					  Drop                -- drop i to leave only acc
 | 
				
			||||||
 | 
					  ]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Several programs that cause errors if run on an empty stack.
 | 
				
			||||||
 | 
					bads = [
 | 
				
			||||||
 | 
					  -- stack underflow errors
 | 
				
			||||||
 | 
					  [Neg],
 | 
				
			||||||
 | 
					  [Push 2, Add],
 | 
				
			||||||
 | 
					  [Push 3, Mul],
 | 
				
			||||||
 | 
					  [Push 4, Drop, Drop],
 | 
				
			||||||
 | 
					  [Dup],
 | 
				
			||||||
 | 
					  [Push 5, Neg, Dig],
 | 
				
			||||||
 | 
					  [If [] []],
 | 
				
			||||||
 | 
					  [While []],
 | 
				
			||||||
 | 
					  -- digging too deep and too greedily, or trying to dig up
 | 
				
			||||||
 | 
					  [Push 6, Push 2, Dig],
 | 
				
			||||||
 | 
					  [Push 7, Push 8, Push 2, Neg, Dig]
 | 
				
			||||||
 | 
					  ]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- * Stack language semantics
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- ** Stack-tracking monad
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | A stack of integers.
 | 
				
			||||||
 | 
					type Stack = [Int]
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | A monad that maintains a stack as state and may also fail.
 | 
				
			||||||
 | 
					--   (A combination of the State and Maybe monads.)
 | 
				
			||||||
 | 
					data StackM a = SM (Stack -> Maybe (a, Stack))
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Run a computation with the given initial stack.
 | 
				
			||||||
 | 
					runWith :: Stack -> StackM a -> Maybe (a, Stack)
 | 
				
			||||||
 | 
					runWith s (SM f) = f s
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					instance Functor StackM where
 | 
				
			||||||
 | 
					  fmap = liftM
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					instance Applicative StackM where
 | 
				
			||||||
 | 
					  pure  = return
 | 
				
			||||||
 | 
					  (<*>) = ap
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					instance Monad StackM where
 | 
				
			||||||
 | 
					  return a = SM $ \s -> Just (a, s)
 | 
				
			||||||
 | 
					  (SM f) >>= g = SM $ \s -> f s >>= \(a, s') -> runWith s' $ g a
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					modify :: (Stack -> Stack) -> StackM ()
 | 
				
			||||||
 | 
					modify f = SM $ Just . ((),) . f
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					gets :: (Stack -> a) -> StackM a
 | 
				
			||||||
 | 
					gets f = SM $ \s -> Just (f s, s)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					fail_ :: StackM a
 | 
				
			||||||
 | 
					fail_ = SM $ const Nothing
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- ** Primitive operations
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Push a value onto the stack.
 | 
				
			||||||
 | 
					push :: Int -> StackM ()
 | 
				
			||||||
 | 
					push i = modify (i:)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Pop a value off the stack and return it.
 | 
				
			||||||
 | 
					pop :: StackM Int
 | 
				
			||||||
 | 
					pop = peek <* modify tail
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					popBool :: StackM Bool
 | 
				
			||||||
 | 
					popBool = (/= 0) <$> pop
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Peek at the value on top of the stack without popping it.
 | 
				
			||||||
 | 
					peek :: StackM Int
 | 
				
			||||||
 | 
					peek = gets safeHead >>= maybe fail_ return
 | 
				
			||||||
 | 
					    where
 | 
				
			||||||
 | 
					        safeHead [] = Nothing
 | 
				
			||||||
 | 
					        safeHead (x:xs) = Just x
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					peekBool :: StackM Bool
 | 
				
			||||||
 | 
					peekBool = (/= 0) <$> peek
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					fromBool :: Bool -> Int
 | 
				
			||||||
 | 
					fromBool = bool 0 1
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Move the ith element from the top of the stack to the top.
 | 
				
			||||||
 | 
					dig :: Int -> StackM ()
 | 
				
			||||||
 | 
					dig i = SM $ \s -> if i > 0 && i <= length s
 | 
				
			||||||
 | 
					                   then let (xs, y:ys) = splitAt (i-1) s
 | 
				
			||||||
 | 
					                        in Just ((), y : xs ++ ys)
 | 
				
			||||||
 | 
					                   else Nothing
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- ** Stack language semantics
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					binop :: (Int -> Int -> Int) -> StackM ()
 | 
				
			||||||
 | 
					binop f = liftM2 f pop pop >>= push
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Monadic semantics of commands.
 | 
				
			||||||
 | 
					cmd :: Cmd -> StackM ()
 | 
				
			||||||
 | 
					cmd (Push i)  = push i
 | 
				
			||||||
 | 
					cmd Drop      = void pop
 | 
				
			||||||
 | 
					cmd Dig       = pop >>= dig
 | 
				
			||||||
 | 
					cmd Dup       = peek >>= push
 | 
				
			||||||
 | 
					cmd Neg       = pop >>= (push . negate)
 | 
				
			||||||
 | 
					cmd Add       = binop (+)
 | 
				
			||||||
 | 
					cmd Mul       = binop (*)
 | 
				
			||||||
 | 
					cmd LEq       = binop ((fromBool.) . (<=))
 | 
				
			||||||
 | 
					cmd (If t e)  = popBool >>= bool (prog e) (prog t)
 | 
				
			||||||
 | 
					cmd (While b) = peekBool >>= bool (return ()) (prog $ b ++ [While b])
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Monadic semantics of programs.
 | 
				
			||||||
 | 
					prog :: Prog -> StackM ()
 | 
				
			||||||
 | 
					prog = mapM_ cmd
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					-- | Run a stack program with an initially empty stack, returning the
 | 
				
			||||||
 | 
					--   resulting stack or an error.
 | 
				
			||||||
 | 
					--
 | 
				
			||||||
 | 
					--   >>> runProg p1
 | 
				
			||||||
 | 
					--   Just [5,5,4]
 | 
				
			||||||
 | 
					--
 | 
				
			||||||
 | 
					--   >>> runProg p2
 | 
				
			||||||
 | 
					--   Just [12,14,13,11,10]
 | 
				
			||||||
 | 
					--
 | 
				
			||||||
 | 
					--   >>> runProg p3
 | 
				
			||||||
 | 
					--   Just [-5,27]
 | 
				
			||||||
 | 
					--
 | 
				
			||||||
 | 
					--   >>> runProg p4
 | 
				
			||||||
 | 
					--   Just [1,0]
 | 
				
			||||||
 | 
					-- 
 | 
				
			||||||
 | 
					--   >>> runProg p5
 | 
				
			||||||
 | 
					--   Just [22]
 | 
				
			||||||
 | 
					--
 | 
				
			||||||
 | 
					--   >>> runProg (Push 10 : fac)
 | 
				
			||||||
 | 
					--   Just [3628800]
 | 
				
			||||||
 | 
					--
 | 
				
			||||||
 | 
					--   >>> all (== Nothing) (map runProg bads)
 | 
				
			||||||
 | 
					--   True
 | 
				
			||||||
 | 
					--
 | 
				
			||||||
 | 
					runProg :: Prog -> Maybe Stack
 | 
				
			||||||
 | 
					runProg = fmap snd . runWith [] . prog
 | 
				
			||||||
							
								
								
									
										27
									
								
								milestone_1_ashish.md
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										27
									
								
								milestone_1_ashish.md
									
									
									
									
									
										Normal file
									
								
							@ -0,0 +1,27 @@
 | 
				
			|||||||
 | 
					Hey, thank you for taking a look! I'll try answer your questions:
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					__Q__: I had a question about why MonadReader was preferred over ReaderT?
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					__A__: `ReaderT` is actually an instance of `MonadReader`! The difference, though, is that the types are kind of simplified. Instead of having to write `ReaderT [Term] ... a`, we just write `m a`. This also allows us to add additional effects to the monad without changing the type signature. For instance, none of the code would change if we wanted to add a state effect via `StateT s`, because the signatures only require constraints on the types, rather than specifying what the types are.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					__Q__: I had a question about how instances for this monad were created.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					__A__: Check out [`LoadingImpl`](https://web.engr.oregonstate.edu/~fedorind/CS583/modules/loadingimpl/), which contains a `PathT` monad transformer which implements `MonadModulePath`. I defined it as a `newtype`
 | 
				
			||||||
 | 
					around a `ReaderT` because you can't have two of the same tranformer in the same monad transformer
 | 
				
			||||||
 | 
					stack, and I didn't want `PathT` to interfere with other `ReaderT`s in the API.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					__Q__: As you rightly mentioned bundling an environment for all operations is a viable option, please let me know if the operations are then stored in a stack format?
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					__A__: Our functions would be kept in a `Map String Definition` or something of that sort. The lookups
 | 
				
			||||||
 | 
					would not be linear time, but probably logarithmic, if that's what you're wondering about.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					__Q__: Kindly let me know if you are referring to type equality?
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					__A__: Well, we are referring to type equality, but within our _object language_ (Maypop), and nor
 | 
				
			||||||
 | 
					our metalanguage (_Haskell_). Although the library you linked would help with equality of _Haskell_
 | 
				
			||||||
 | 
					types, it wouldn't help us with _Maypop_.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					__Q__: I think using some kind of plugin for haskell might help in doing tactics.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					__A__: It would if we were trying to add tactics to Haskell, but we're trying to add tactics to
 | 
				
			||||||
 | 
					Maypop. We have full control of the language; the real question is, what will our design be like?
 | 
				
			||||||
							
								
								
									
										224
									
								
								milestone_1_feedback.md
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										224
									
								
								milestone_1_feedback.md
									
									
									
									
									
										Normal file
									
								
							@ -0,0 +1,224 @@
 | 
				
			|||||||
 | 
					# Jack Attack
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					* Your comments are very thorough! Have you, however, consider the special
 | 
				
			||||||
 | 
					"haddock" syntax for your documentation? For instance, in your `Object` record,
 | 
				
			||||||
 | 
					you clearly describe what each field does. If you used the "haddock" syntax
 | 
				
			||||||
 | 
					(maybe something like `--^ comment goes here`), you'd be able to generate
 | 
				
			||||||
 | 
					static documentation pages much like those you see on hackage or stackage.
 | 
				
			||||||
 | 
					Those are useful because they allow the user to browse the documentation
 | 
				
			||||||
 | 
					for your package from the web before deciding to install and use it. And,
 | 
				
			||||||
 | 
					of course, I think it's nicer to look at a web page than comments!
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					* There's a lot of duplicate functionality in your `doTimedTransform`
 | 
				
			||||||
 | 
					  function compared to your `doTransform` function. It seems almost
 | 
				
			||||||
 | 
					  as though there should be _one_ function that takes care of both
 | 
				
			||||||
 | 
					  the interpolation and the transformation; perhaps `doTransform`
 | 
				
			||||||
 | 
					  can take an argument `0.0..1.0` of "progress", and go from there.
 | 
				
			||||||
 | 
					  This will save you the trouble of unpacking and repacking your
 | 
				
			||||||
 | 
					  `Transformation` objects. Even if you don't go for that approach,
 | 
				
			||||||
 | 
					  however, there's still an improvement you can make. Rather than making
 | 
				
			||||||
 | 
					  your `doTimedTransform` function do _everything_, you may want to define
 | 
				
			||||||
 | 
					  a function
 | 
				
			||||||
 | 
					  
 | 
				
			||||||
 | 
					  ```Haskell
 | 
				
			||||||
 | 
					  tween :: Object -> Float -> Transformation -> Transformation
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  This function would do _kind of_ like what your `doTimeTransform` does:
 | 
				
			||||||
 | 
					  it would interpolate the transformation given the current object and
 | 
				
			||||||
 | 
					  the "progress" within the transformation. The difference, though,
 | 
				
			||||||
 | 
					  is that it will not actually _apply_ the transformation, but create
 | 
				
			||||||
 | 
					  a new one (much like you're already doing in `doTimedTransform` anyway).
 | 
				
			||||||
 | 
					  You would then be able to feed this transformation into `doTransform`,
 | 
				
			||||||
 | 
					  and it would work as expected. The advantage here is that you won't have
 | 
				
			||||||
 | 
					  to be writing duplicate code for stuff like:
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					  doTransform (Combine xs) $ doTransform x obj
 | 
				
			||||||
 | 
					  doTimedTransform (seconds, x) (doTimedTransform (seconds, Combine xs) obj elapsed) elapsed
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					  
 | 
				
			||||||
 | 
					  There's a fairly clear similarity (and consequently duplication) here, and
 | 
				
			||||||
 | 
					  that's what I think my approach would suggest.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  And there's one more thing: does `tween` _really_ need access to the object
 | 
				
			||||||
 | 
					  being animated? It sure seems to if your transformations are "absolute",
 | 
				
			||||||
 | 
					  like "move to (1,2)". This "absoluteness" of transformations forces you to
 | 
				
			||||||
 | 
					  use `obj` in `doTimedTransform`, and would also force you to use it in
 | 
				
			||||||
 | 
					  `tween`. But if your transformations were _delta based_ ("move left 1, up t2"), your `tween` could be only a function of the current "progress" `Float`:
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					  tween :: Float -> Transformation -> Transformation
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  This may help clean up some of the code, and it also allows for an
 | 
				
			||||||
 | 
					  interesting experiment: what if you compose `tween` with various
 | 
				
			||||||
 | 
					  functions `Float -> Float`? For instance, you could compose it with
 | 
				
			||||||
 | 
					  `\x -> x * x`, which I think would make your animation start out slow
 | 
				
			||||||
 | 
					  and speed up at the end. You may be able to use this to play around
 | 
				
			||||||
 | 
					  with various ways of animating your objects that are used in "actual"
 | 
				
			||||||
 | 
					  animation: from what I know, linear transformations are not as common
 | 
				
			||||||
 | 
					  as, say, sigmoid ones (animation starts slow, gets fast in the middle,
 | 
				
			||||||
 | 
					  and slows down again at the end).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					* I would try to factor out the "seconds" part of your calculations as soon
 | 
				
			||||||
 | 
					as possible. In my opinion, it would be clearer to pass around a "percentage
 | 
				
			||||||
 | 
					completed" float, especially if you don't have any other dependence on
 | 
				
			||||||
 | 
					the current time.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					* Cody is right, you do have a couple of places that can be used by folds
 | 
				
			||||||
 | 
					  or other higher order functions. For instance, `getAniLength` is just
 | 
				
			||||||
 | 
					  `sum . map fst`, and the `Combine` case of `doTransform` is something
 | 
				
			||||||
 | 
					  like `foldr (flip doTransform) obj (x:xs)`.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					* Are transformations a monoid? I suspect that they are, with `mempty = Wait`,
 | 
				
			||||||
 | 
					`mappend x y = Combine [x,y]`, and `mconcat = Combine`. I don't know
 | 
				
			||||||
 | 
					if this will be useful, but it's always nice to have access to more
 | 
				
			||||||
 | 
					standard library functions!
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					* I'm not sure I follow the `AST` vs `Lib` modules. They both seem
 | 
				
			||||||
 | 
					to have _something_ in mind, but I can't quite figure out how they work
 | 
				
			||||||
 | 
					together. Does the `AST` eventually produce a `Transformation`? I just
 | 
				
			||||||
 | 
					don't really know what to make of it!
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					About your design questions:
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					* Q1: It would be cool if you had a slider that lets you play
 | 
				
			||||||
 | 
					 the animation back and forward (or at an arbitrary point in time).
 | 
				
			||||||
 | 
					 I think it may help in debugging:
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					 > Why did my object just make a 360 and walk away?
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					 It would be even better if you could label your transformations
 | 
				
			||||||
 | 
					 with the function / piece of code that induced them, so that
 | 
				
			||||||
 | 
					 at any point, you can kind of see what part of your code is
 | 
				
			||||||
 | 
					 causing the current transformation.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					* Q2: At the implementation level, you may need to replace the
 | 
				
			||||||
 | 
					  `Float` argument of `doTransform` with an `Env` argument,
 | 
				
			||||||
 | 
					  which may be a record-like thing that contains the current
 | 
				
			||||||
 | 
					  mouse position, the current time, and so on. You'd then
 | 
				
			||||||
 | 
					  thread it as before.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  At a language level, things are more interesting. Have you
 | 
				
			||||||
 | 
					  looked into [functional reactive programming](https://en.wikipedia.org/wiki/Functional_reactive_programming)?
 | 
				
			||||||
 | 
					  You may be interested in encoding transformations declaratively, given, say
 | 
				
			||||||
 | 
					  the current mouse position, time, etc. as input. Your programs would then
 | 
				
			||||||
 | 
					  be descriptions of how to convert these inputs into figures on the screen.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  [Elm](elm-lang.org) is a language that implements quasi-FRP. It doesn't deal with
 | 
				
			||||||
 | 
					  continuous inputs like you would be, but it encodes programs as transition
 | 
				
			||||||
 | 
					  functions (`Event -> State -> State`). You may be interested in adapting
 | 
				
			||||||
 | 
					  a similar approach - it's a nice way to deal with "imperative" environments
 | 
				
			||||||
 | 
					  from a functional language.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					* Q3: This is a tough one! I think you can come up with a textual functional
 | 
				
			||||||
 | 
					language that can be used for your domain, but I'd be thrilled to see how
 | 
				
			||||||
 | 
					you may incorporate visual (scratch-like) elements into your project. At this
 | 
				
			||||||
 | 
					point, though, I can't help but wonder: would you have time to implement something
 | 
				
			||||||
 | 
					like Scratch-like blocks? We're in week 8, after all. That would be a very graphical
 | 
				
			||||||
 | 
					type of user interface, and I can't personally imagine defining a UI from scratch,
 | 
				
			||||||
 | 
					in Haskell, using only graphics library primitives. Of course, you're probably
 | 
				
			||||||
 | 
					more versed than I am in Haskell's graphics tooling, but it seems to me like
 | 
				
			||||||
 | 
					a fairly daunting task.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					# Escape
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					* I played with your game for a bit, pretty cool! I think you did a nice job with the textual
 | 
				
			||||||
 | 
					  users interface; it feels pretty much like I'd expect a command line interface to work.
 | 
				
			||||||
 | 
					  I did run into an error on my first playthrough, and decided not to try again: `Prelude.head: empty list`.
 | 
				
			||||||
 | 
					  This happened because I typed `search` without any arguments. Now, I understand that
 | 
				
			||||||
 | 
					  what I did was an incorrect command, but crashing the game doesn't seem like the right thing to do!
 | 
				
			||||||
 | 
					  `head` is a dangerous function; I think that if Haskell were redesigned today, from the ground
 | 
				
			||||||
 | 
					  up, this function would no longer have type `[a] -> a`. In general, exceptions in Haskell are
 | 
				
			||||||
 | 
					  a bit of an antipattern, because they're not indicated by the types (how could you know `head` throws
 | 
				
			||||||
 | 
					  an exception), but also because they're cumbersome to work with!
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  Languages defined after Haskell actually define `head` with a `Maybe`. Here's the [Idris version](https://github.com/idris-lang/Idris-dev/blob/a13caeb4e50d0c096d34506f2ebf6b9d140a07aa/libs/prelude/Prelude/List.idr#L128-L130),
 | 
				
			||||||
 | 
					  and here's the [Elm version](https://package.elm-lang.org/packages/elm/core/latest/List#head). You
 | 
				
			||||||
 | 
					  may want to define your own head function, `safeHead :: [a] -> Maybe a`! You can then use pattern
 | 
				
			||||||
 | 
					  matching or the `maybe` function to properly handle the error that occurs when the user doesn't give
 | 
				
			||||||
 | 
					  the command enough arguments. You could, for instance, print "Search what?" when a user types in "search".
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					* This is a minor nitpick, but I'm pretty sure `snake_case` is not the preferred standard
 | 
				
			||||||
 | 
					  for Haskell variable names. Your records (and module names!) should be in `camelCase`.
 | 
				
			||||||
 | 
					  In fact, my linter plugin _covers_ the screen with warnings about style when it sees your code!
 | 
				
			||||||
 | 
					* `Funcfunctor` is a funny name for a typeclass. It seems to imply that `t` is a functor; however,
 | 
				
			||||||
 | 
					  `Functor` is a type constructor class, whereas your code treats `t` as just a type, not a type
 | 
				
			||||||
 | 
					  constructor! In fact, I'm really not sure what to make of the word `Funcfunctor`. What does
 | 
				
			||||||
 | 
					  it mean?
 | 
				
			||||||
 | 
					* On the other hand, I think that this is a good application of type classes. If you want to
 | 
				
			||||||
 | 
					  print a variety of different objects on the screen in your command line game, defining a common
 | 
				
			||||||
 | 
					  type class with the various properties of these objects is a great idea. You can certainly
 | 
				
			||||||
 | 
					  get a very consistent interface this way!
 | 
				
			||||||
 | 
					* In `Escape_funs`, a lot of your pattern matching code can be significantly simplified! You always write
 | 
				
			||||||
 | 
					  out stuff like `Object {object_id=id, object_name=...}`, but use only one of these variables (for instance, `id`).
 | 
				
			||||||
 | 
					  Instead, you can _only_ write `Object {object_id=id}` -- that's it! You don't need to manually enumerate every single
 | 
				
			||||||
 | 
					  key in your records to pattern match on them.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  A cute fun fact of this notation: it's "preferred style" according to Haskell's linter to rewrite code like `(Constructor _ _ _ _)`
 | 
				
			||||||
 | 
					  (pattern matching on a data type and ignoring all its fields) as `Constructor{}`.
 | 
				
			||||||
 | 
					* `foldr (||) False (map (==(get_key obj)) list)` is good use of a fold a map, but it also
 | 
				
			||||||
 | 
					  corresponds to the Haskell function [`any`](http://zvon.org/other/haskell/Outputprelude/any_f.html): 
 | 
				
			||||||
 | 
					  `any (==(get_key obj)) list`.
 | 
				
			||||||
 | 
					* Notice how your `run_code` is a bit fragile: your `help` function prints out all the commands available
 | 
				
			||||||
 | 
					  to the user, while `run_code` actually implements these commands. It must be very easy to
 | 
				
			||||||
 | 
					  edit `run_code` to add a new command, while forgetting to update `help`. You may be able
 | 
				
			||||||
 | 
					  to work around this by defining a `Command` data structure: maybe it'll have a `description`
 | 
				
			||||||
 | 
					  field that you print to the user, and another `action` filed that's maybe some monad like `IO ()`
 | 
				
			||||||
 | 
					  that actually performs the actions that your command does. Then, you can have a global
 | 
				
			||||||
 | 
					  list of commands `commands :: Map String Command`, which contains all the allowed commands
 | 
				
			||||||
 | 
					  in your game. Your `help` function would go through this `commands` variable and print
 | 
				
			||||||
 | 
					  out the `description` field of every available command; on the other hand, the `run_code`
 | 
				
			||||||
 | 
					  function would read a command from the user, look it up in `commands`, and try to execute
 | 
				
			||||||
 | 
					  the `action` field.
 | 
				
			||||||
 | 
					* Notice that you're explicitly handling your application's state: you will need to pass
 | 
				
			||||||
 | 
					  the correct house to `run_code` every time, which means that for each command, you need
 | 
				
			||||||
 | 
					  a separate call to `run_code` with whatever house that command puts your player in.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  An alternative approach is to handle state _implicitly_. You won't need to take a `house`
 | 
				
			||||||
 | 
					  argument explicitly, and you therefore won't have to explicitly pass it to your recursive
 | 
				
			||||||
 | 
					  calls to `run_code`. In your case, this would be best done with a `State` monad, since
 | 
				
			||||||
 | 
					  the current location of the player is, well, a piece of state.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  The question, though, becomes: how the heck do you incorporate a state monad into your
 | 
				
			||||||
 | 
					  `IO`-based code? The answer to that is the `StateT` _monad transformer_. We haven't learned
 | 
				
			||||||
 | 
					  about these in class just yet, but we will soon, and I think it would serve you well! Instead
 | 
				
			||||||
 | 
					  of making your code of type `IO ()` (what it currently is), you'd use something like
 | 
				
			||||||
 | 
					  `StateT [Room] IO ()`. Your calls to `putStrLn` would have to go through a `liftIO`,
 | 
				
			||||||
 | 
					  but you'd also gain access to functions `get` and `put`, which are the functions of the
 | 
				
			||||||
 | 
					  State monad that we have covered in class. Then, whenever your user goes to a different
 | 
				
			||||||
 | 
					  house, you'd run `put new_house`, and whenever you need to check the current location
 | 
				
			||||||
 | 
					  of the player, you'd run `get`. 
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  You may then incorporate other monad transformers into this implementation; I think
 | 
				
			||||||
 | 
					  of interest to you would be `ExceptT` (which is __not the same as Haskell's exceptions
 | 
				
			||||||
 | 
					  that I mentioned in my first bullet point!__), which might help you exit out of your
 | 
				
			||||||
 | 
					  code when your player types "exit".
 | 
				
			||||||
 | 
					* By the way, you should probably explicitly type out the signatures of your function;
 | 
				
			||||||
 | 
					  I think that's considered good style. For instance, for `run_code`, you'd write:
 | 
				
			||||||
 | 
					  
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					  run_code :: Player -> [Room] -> IO ()
 | 
				
			||||||
 | 
					  run_code plauer house = ...
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					Your questions:
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					* Q1: Hey, I brought up `StateT` and `ExceptT` and monad transformers in general earlier!
 | 
				
			||||||
 | 
					  Check them out. I think you may find them useful for what you're doing. The only difficulty
 | 
				
			||||||
 | 
					  is that you really need to see a few examples of code before-and-after the use of State
 | 
				
			||||||
 | 
					  and Exception monads to be comfortable in applying them (at least for me! It took me a while
 | 
				
			||||||
 | 
					  to properly understand monads, and more time to understand monad transformers).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					* Q2: Haskell's `IO` monad has `readFile` and `writeFile` methods, but these may be a bit
 | 
				
			||||||
 | 
					  basic for your taste. You may be interested in various formats like [INI](https://hackage.haskell.org/package/ini-0.4.1/docs/Data-Ini.html)
 | 
				
			||||||
 | 
					  or even JSON (for which you can use something like [Aeson](https://hackage.haskell.org/package/aeson-1.5.6.0/docs/Data-Aeson.html),
 | 
				
			||||||
 | 
					  especially its `encodeFile` and `decodeFile` methods).
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					I'm running out of steam writing this comment, but I may post a follow up if I think of anything else!
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					__Eric, if you're reading this:__ have I been evangelizing monad transformers too much? I feel like
 | 
				
			||||||
 | 
					I have been. It would be good to know if I'm being overzealous; everything starts to look like a nail
 | 
				
			||||||
 | 
					when all you have is a hammer!
 | 
				
			||||||
							
								
								
									
										195
									
								
								milestone_2_feedback.md
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										195
									
								
								milestone_2_feedback.md
									
									
									
									
									
										Normal file
									
								
							@ -0,0 +1,195 @@
 | 
				
			|||||||
 | 
					## Orange Sudoku
 | 
				
			||||||
 | 
					* Could you perhaps avoid the (unsafe) list indexing using (!!) in Sudoku? Although it's difficult
 | 
				
			||||||
 | 
					  to represent the finite-length list of elements in Haskell, you may be able to tweak your representation
 | 
				
			||||||
 | 
					  of the sudoku puzzle to avoid having to use (!!). For instance, what if you had:
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  ```Haskell
 | 
				
			||||||
 | 
					  type Array2d a = [[a]]
 | 
				
			||||||
 | 
					  type Cell = Array2d Int
 | 
				
			||||||
 | 
					  type Sudoku = Array2d Cell
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					  
 | 
				
			||||||
 | 
					  __Disclaimer: all type signatures and functions below are written without a Haskell
 | 
				
			||||||
 | 
					  interpreter at hand. There are probably errors - I can't always write Haskell without
 | 
				
			||||||
 | 
					  feedback.__.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  That is, your top-level data structure would be a 3x3 grid of 3x3 "cells". You could then extract
 | 
				
			||||||
 | 
					  your `mapAllPairsM_ ...` function into something like `noneEqual :: [a] -> CSP ()` (the exact
 | 
				
			||||||
 | 
					  signature is not correct since I didn't have enough time to study the types of functions in the CSP
 | 
				
			||||||
 | 
					  library. Then, you can have
 | 
				
			||||||
 | 
					  
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					  checkCell :: Cell -> CSP ()
 | 
				
			||||||
 | 
					  checkCell = noneEqual . concat
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  checkCells :: Sudoku -> CSP ()
 | 
				
			||||||
 | 
					  checkCells = mapM_ (mapM_ checkCell)
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  Of course, you still need to extract rows. You can do it with something like the following:
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					  mergeRow :: [Cell] -> [[Int]]
 | 
				
			||||||
 | 
					  mergeRow = foldr (zipWith (++)) []
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  allRows :: Sudoku -> [[Int]]
 | 
				
			||||||
 | 
					  allRows = concatMap mergeRow
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  And then, your two remaining constraints can be solved as:
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					  checkRows :: Sudoku -> CSP ()
 | 
				
			||||||
 | 
					  checkRows = mapM_ noneEqual . allRows
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  checkColumns :: Sudoku -> CSP ()
 | 
				
			||||||
 | 
					  checkColumns = mapM_ noneEqual . transpose . allRows
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  And finally, your entire Sudoku checker constraint would be:
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					  check :: Sudoku -> CSP ()
 | 
				
			||||||
 | 
					  check s = checkCells s >> checkRows s >> checkColumns s
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  Look ma, no mention of size whatsoever! In fact, there's no mention of numbers at all in this code.
 | 
				
			||||||
 | 
					  There is, of course, the assumption in all the above code that your cells are always NxN. 
 | 
				
			||||||
 | 
					* Your `cells` function seems to be unused. I actually prefer this function to the rest of your code,
 | 
				
			||||||
 | 
					  because it doesn't have as many hardcoded numbers (like `0, 3, 6,`). On the other hand, your actual
 | 
				
			||||||
 | 
					  solver hardcodes a _lot_ of numbers, which means that your code is not generalizeable to higher
 | 
				
			||||||
 | 
					  dimensions, even though there's nothing inherently difficult about generalizing the sudoku solving problem.
 | 
				
			||||||
 | 
					* I really like your definition of `mapAllPairsM_`! This seems like the perfect level of abstraction for me,
 | 
				
			||||||
 | 
					  and the typeclass constraint for `Monad` makes it more general. Nice!
 | 
				
			||||||
 | 
					* It looks like you actually implemented your own constraint solver in `CSP.hs`. Why didn't you use this for
 | 
				
			||||||
 | 
					  your Sudoku itself? It seems as though `NQueens` used your `CSP` module, and it seems like Sudoku _should_
 | 
				
			||||||
 | 
					  work with binary constraint systems (each two variable has to take on assignments (1, 2), (2, 1), (1, 3), ...). 
 | 
				
			||||||
 | 
					* In general, I don't know if I'm a fan of using integers and Haskell's range syntax for assigning variables.
 | 
				
			||||||
 | 
					  It just seems to.... hardcoded? Maybe abstraction has fried my brain, and I'm incapable of perceiving any
 | 
				
			||||||
 | 
					  type that is not polymorphic, but I _do_ think it should be possible, to, say, use string / character / byte
 | 
				
			||||||
 | 
					  variables. You could then represent `vars` as `Set a`, and your domain as `[(a, Set b)]` (where `a` is the
 | 
				
			||||||
 | 
					  type of variable, and `b` is the type of elements in the domain). You could probably even get away with
 | 
				
			||||||
 | 
					  domains that contain different types (for instance, var `a` is an Int while var `b` is a String) if you
 | 
				
			||||||
 | 
					  used [existential types](https://wiki.haskell.org/Existential_type) (did we learn these in class? I saw
 | 
				
			||||||
 | 
					  other groups using them, but I don't remember hearing Eric talk about them...). 
 | 
				
			||||||
 | 
					* Hmm, your `load` function is undefined. You probably want to implement that in time for the final submission.
 | 
				
			||||||
 | 
					* You clearly did great work with the constraint solver! Your `NQueens` solution is very short in Haskell.
 | 
				
			||||||
 | 
					  I also really enjoy watching the results print out on the screen. It is quite slow though; is that inherent
 | 
				
			||||||
 | 
					  to CSP, or do you think your implementation could use some work? You should check out how to do _profiling_
 | 
				
			||||||
 | 
					  in Haskell - it's one of the most important skills industry Haskell jobs seem to look for.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					Nice work, and have a great day!
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					## Ping Pong
 | 
				
			||||||
 | 
					* I wasn't able to run your code, becasue I am on Linux and your instructions did not include
 | 
				
			||||||
 | 
					  information about how to set up on a Linux machine. It's no problem, though - I know what
 | 
				
			||||||
 | 
					  a pain it is to distribute graphics libraries etc. to users.
 | 
				
			||||||
 | 
					* As soon as I open `Data.hs`, my Haskell linter complains: you're not using camel case!
 | 
				
			||||||
 | 
					  The proper varible naming convention is, for example, `winScore`, not `win_score`. It's _very_
 | 
				
			||||||
 | 
					  uncommon to use anything else, and when other things _are_ used, it's usually for good reason!
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  In fact, it seems like your code does not itself follow a consistent format. You have `sceneState`,
 | 
				
			||||||
 | 
					  but then you have `ai_mod`.
 | 
				
			||||||
 | 
					* There's a lot of repetition in your `PPG` data structure. Particularly aggravating is the
 | 
				
			||||||
 | 
					  duplication of many fields: `bat1` and `bat2`, `bat1height` and `bat2height`, and so on.
 | 
				
			||||||
 | 
					  Could you, perhaps, define a second data structure that contains all the common information?
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					  data PlayerData = PlayerData
 | 
				
			||||||
 | 
					      { bat :: Float
 | 
				
			||||||
 | 
					      , batState :: Int
 | 
				
			||||||
 | 
					      , batHeight :: Float
 | 
				
			||||||
 | 
					      , score :: Int
 | 
				
			||||||
 | 
					      }
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  And then, you'd have:
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					  data PPG = Game
 | 
				
			||||||
 | 
					    { ballPos :: (Float, Float)    -- ^ Pong ball (x, y) Position.
 | 
				
			||||||
 | 
					    , ballVel :: (Float, Float)     -- ^ Pong ball (x, y) Velocity. 
 | 
				
			||||||
 | 
					    , sceneState :: Int                -- 0: Instruction, 1: Play, 2: End
 | 
				
			||||||
 | 
					    , ballspeed :: Float
 | 
				
			||||||
 | 
					    , ai_mod :: Int
 | 
				
			||||||
 | 
					    , player1 :: PlayerData
 | 
				
			||||||
 | 
					    , player2 :: PlayerData
 | 
				
			||||||
 | 
					    } deriving Show
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					* It seems like you're using integers to represent states! I see the comment:
 | 
				
			||||||
 | 
					  
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					  -- 0: Instruction, 1: Play, 2: End
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  This is not at all idiomatic in Haskell! It is very easy to define data types in Haskell,
 | 
				
			||||||
 | 
					  and that's precisely what you should do:
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					  data SceneState = Instruction | Play | End deriving (Eq, Show)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  -- ...
 | 
				
			||||||
 | 
					      , sceneState :: SceneState
 | 
				
			||||||
 | 
					  -- ---
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  Instead of using `sceneState game == 0`, you'd then use something like
 | 
				
			||||||
 | 
					  `sceneState game == Instruction`, or better yet, you'd use pattern matching! Pattern matching
 | 
				
			||||||
 | 
					  really _is_ the bread and butter of Haskell programming. I see you do use pattern matching
 | 
				
			||||||
 | 
					  on `bat1state` (which should _also_ be a data type, like `BatState`), but if you turn
 | 
				
			||||||
 | 
					  on the standard warnings in GHCI (by pasing `--ghci-options "-W"` to `stack`), you'll
 | 
				
			||||||
 | 
					  see that this pattern __is not total__! It only covers the cases `0`, `1`, and `2`,
 | 
				
			||||||
 | 
					  but it doesn't cover the cases of `3`, `4`, and so on, which are valid values of `Int`!
 | 
				
			||||||
 | 
					  Even though you _know_ that the number can only be `0-2`, it's much better practice
 | 
				
			||||||
 | 
					  (and far more idiomatic) to move these kind of invariants into our type system, so
 | 
				
			||||||
 | 
					  that it's _impossible_ to write incorrect code. I think the general name for this approach
 | 
				
			||||||
 | 
					  is [make illegal states unrepresentable](https://fsharpforfunandprofit.com/posts/designing-with-types-making-illegal-states-unrepresentable/).
 | 
				
			||||||
 | 
					* Your `render` function is very long! I count `45` lines (albeit with some white space). It's
 | 
				
			||||||
 | 
					  also full of harcoded constants, like `185`, `110`, and so on.
 | 
				
			||||||
 | 
					  This is the [magic number](https://en.wikipedia.org/wiki/Magic_number_(programming%29) antipattern!
 | 
				
			||||||
 | 
					  You can try extracting them into some constants, or better yet, positioning them relatively (using
 | 
				
			||||||
 | 
					  information such as text height, screen height, and some basic typography-type math) so that
 | 
				
			||||||
 | 
					  it fits many screen sizes and configurations!
 | 
				
			||||||
 | 
					* You may be usign too many parentheses; here's a screenshot of my editor viewing one of your source code files!
 | 
				
			||||||
 | 
					  As you can see, there's quite a lot of yellow, mostly from unnecessary uses of `(` and `)`.
 | 
				
			||||||
 | 
					* Not your code duplicaton in `y''` and `y'''`. They're pretty much the same function, except one
 | 
				
			||||||
 | 
					  computes the y-axis for the `bat1`, and the other computes it for `bat2`. This amount of code
 | 
				
			||||||
 | 
					  duplication is a smell - you would be able to reduce this duplication to a single function if
 | 
				
			||||||
 | 
					  you were to extract your bat data into `PlayerData` records as I mentioned in my earlier comment.
 | 
				
			||||||
 | 
					* This may be controversial, but instead of using `if then/else if` chains as you do, you can try
 | 
				
			||||||
 | 
					  pattern matching on the boolan values (maybe something like this):
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					  case (leftout (ballPos game), rightout (ballPos game)) of
 | 
				
			||||||
 | 
					      (True, _) -> game {p1score = (p1score game) + 1, ballPos = (0, 0), ballVel = (-30, -40) }
 | 
				
			||||||
 | 
					      (_, True) -> game {p2score = (p2score game) + 1, ballPos = (0, 0), ballVel = (-30, -40) }
 | 
				
			||||||
 | 
					      _ -> game
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					  
 | 
				
			||||||
 | 
					  I think this is easier to follow than variously indented `if`/`else` chains.
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					* In the segment of code above, you are also repeating your code for resetting the ball position
 | 
				
			||||||
 | 
					  and velocity. What about a function:
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					  resetBall :: PPG -> PPG
 | 
				
			||||||
 | 
					  resetBall game = game { ballPos = (0, 0), ballVel = (-30, -40) }
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  Then, the above code becomes:
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					  case (leftout (ballPos game), rightout (ballPos game)) of
 | 
				
			||||||
 | 
					      (True, _) -> resetBall $ game {p1score = (p1score game) + 1 }
 | 
				
			||||||
 | 
					      (_, True) -> resetBall $ game {p2score = (p2score game) + 1 }
 | 
				
			||||||
 | 
					      _ -> game
 | 
				
			||||||
 | 
					  ```
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					  And now, it's much clearer what each case does! If the ball is out
 | 
				
			||||||
 | 
					  on either side, you reset its position, and add points to the
 | 
				
			||||||
 | 
					  other player!
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					* In `outofBound` and elsewhere, nice use of `where`!
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					* Your comments are quite good, and you even used the `^--` Haddoc-style
 | 
				
			||||||
 | 
					  comments in various places! Nice job with that, too.
 | 
				
			||||||
		Loading…
	
		Reference in New Issue
	
	Block a user