Skip to content

Instantly share code, notes, and snippets.

@JackTheEngineer
Last active May 27, 2018 00:50
Show Gist options
  • Save JackTheEngineer/e34ccd73d8dccd93c3d6313245256f9d to your computer and use it in GitHub Desktop.
Save JackTheEngineer/e34ccd73d8dccd93c3d6313245256f9d to your computer and use it in GitHub Desktop.
Monadic Computations with named parameters in functions
import Control.Monad
import Control.Applicative
import Data.List
type KnightPos = (Int, Int)
nextMoves c r = [(c+2,r-1), (c+2,r+1),(c-2,r-1),(c-2,r+1),
(c+1,r-2),(c+1,r+1),(c-1,r-2),(c-1,r+2)]
inField c r = (c `elem` [1..8] && r `elem` [1..8])
moveKnight :: KnightPos -> [KnightPos]
moveKnight (c,r) = nextMoves c r >>= (\(c', r') -> guard(inField c' r') >> return (c',r'))
pathIn3 :: KnightPos -> KnightPos -> [[KnightPos]]
pathIn3 start end = return start >>= \p0 -> moveKnight p0
>>= \p1 -> moveKnight p1
>>= \p2 -> moveKnight p2 >>=
\p3 -> guard(p3 == end)
>> return([p1, p2, p3])
-- Whereas something like this would be much nicer, but does not give the parameter to the function a name
-- pathIn3 start end times = return start >>= foldr <=< (replicate times (inN 1))
@glguy
Copy link

glguy commented May 27, 2018

module Help where

import Control.Monad
import Control.Applicative
import Data.List

type KnightPos = (Int, Int)

nextMoves c r = [(c+2,r-1), (c+2,r+1),(c-2,r-1),(c-2,r+1),
                 (c+1,r-2),(c+1,r+1),(c-1,r-2),(c-1,r+2)]

inField c r = (c `elem` [1..8] && r `elem` [1..8])

moveKnight :: KnightPos -> [KnightPos]
moveKnight (c,r) = nextMoves c r >>= (\(c', r') -> guard(inField c' r') >> return (c',r'))


pathInN :: Int -> KnightPos -> KnightPos -> [[KnightPos]]
pathInN 0 start end = [] <$ guard (start == end)
pathInN n start end =
  do next <- moveKnight start
     rest <- pathInN (n-1) next end
     return (next:rest)

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment