I was going through "Learn Yourself a Haskell" and am trying to implement the "Heathrow to London" problem [1] in a Monadic way (instead of folds or explicit recursions). [1] http://learnyouahaskell.com/functionally-solving-problems#heathrow-to-london
My question is this: both instance Applicative Route where
and instance Applicative Route a where
makes GHC complain as below. So including a type parameter is wrong, but not including is also wrong. How do I overcome this by minimal change to the code (its implementation idea)? See implementation below the GHC error.
Prelude> :r
[1 of 1] Compiling Main ( heathrowToLondon.hs, interpreted )
heathrowToLondon.hs:70:10: error:
• Expecting one fewer argument to ‘Applicative Route’
Expected kind ‘k0 -> Constraint’,
but ‘Applicative Route’ has kind ‘Constraint’
• In the instance declaration for ‘Applicative Route a’
Failed, modules loaded: none.
Prelude> :r
[1 of 1] Compiling Main ( heathrowToLondon.hs, interpreted )
heathrowToLondon.hs:70:10: error:
• The type synonym ‘Route’ should have 1 argument, but has been given none
• In the instance declaration for ‘Applicative Route’
Failed, modules loaded: none.
My implementation was this: think of each street (one street above, one street below and the crossing avenue) costs as a Street
, then think of Route
as all the route until now as well as the cumulative costs of going Up
or Down
next. Then, mempty
or pure
for Route
would be something like ([], (0,0))
. We define a binary operation join
to Route
, then we can get >=
by using fmap
and join
. Partial code below:
{-# LANGUAGE TypeSynonymInstances #-}
import Data.List
import Data.List.Extra (chunksOf)
import Control.Monad
-- Try this:
-- solvePath [50, 10, 30, 5, 90, 20, 40, 2, 25, 10, 8]
data Path = Up | Down deriving (Show, Eq, Read)
type Costs a = (a, a)
type Street a = [a]
type Route a = ([Path], Costs a)
-- Monadic!?
toRoute :: (Num a, Ord a) => Street a -> Route a
toRoute [x,y,z] = ([], (min x (y+z), min y (x+z)))
toRoute _ = ([], (0,0))
instance Applicative Route where -- putting or not putting this `a` here doesn't work
pure x = toRoute x -- turns [1,2,5] Street value
f <*> g = undefined
-- Irrelevant to this question but does the job
-- Using explicit recursion
solvePath :: (Num a, Ord a) => Street a -> [Path]
solvePath xs = reverse . crossStreet (0,0) [] $ 0:xs
crossStreet :: (Num a, Ord a) => Costs a -> [Path] -> Street a -> [Path]
crossStreet (a,b) rd street
| null street = rd
| a > b = crossStreet (a',b') (Down:rd) street'
| a == b && a' >= b' = crossStreet (a',b') (Down:rd) street'
| otherwise = crossStreet (a',b') (Up:rd) street'
where (a',b') = (a + min x (y+z), b + min y (x+z))
(x:y:z:street') = street
-- Using folds
solvePath' = reverse . fst . foldl' crossStreet' ([], (0,0)) . chunksOf 3 . (0:)
crossStreet' :: (Num a, Ord a) => Route a -> Street a -> Route a
crossStreet' (ps, (a,b)) [] = (ps, (a,b))
crossStreet' (ps, (a,b)) [x,y,z] = (ps', (a', b'))
where (a',b') = (a + min x (y+z), b + min y (x+z))
ps' = p:ps
p | a > b || ((a==b) && a' >= b') = Down
| otherwise = Up
Edit #1
Based on comments, I changed the definition for route into RouteM
using data
, and now the original complaint is solved. However, I still need to figure out how to implement the <*>
though.
data RouteM a = RouteM {getPath :: [Path], getCost :: Costs a} deriving (Show, Eq, Read)
-- Monadic!?
toRouteM :: (Num a, Ord a) => Street a -> RouteM a
toRouteM [x,y,z] = RouteM [] (min x (y+z), min y (x+z))
toRouteM _ = RouteM [] (0, 0)
instance Functor RouteM where -- putting or not putting this `a` here doesn't work
fmap f r = RouteM (getPath r) (f . fst $ getCost r, f . snd $ getCost r)
instance Applicative RouteM where -- putting or not putting this `a` here doesn't work
pure x = RouteM [] (x, x)
f <*> r = undefined