Skip to content

Instantly share code, notes, and snippets.

@nkpart
Last active June 7, 2016 06:13
Show Gist options
  • Save nkpart/9f41660b4412c320344ee7ca6aa06c11 to your computer and use it in GitHub Desktop.
Save nkpart/9f41660b4412c320344ee7ca6aa06c11 to your computer and use it in GitHub Desktop.
module Foo where
import Data.Functor.Identity
-- | OK
--
-- We are going to build 2 functions
-- * something that collects all the items in a list of futures
-- * something that recursively gets all the search results from an
-- initial search result
-- A fake Future, it's a monad and functor like Future is
type Future a = Identity a
type Item = Int
type Link = String
nextPage :: Link -> Future SearchResult
nextPage = error "implement please"
data SearchResult = SearchResult {
searchResultItems ::[Item],
searchResultNextLink :: Maybe Link
}
-- | Function 1 - not much too it
allItems :: [SearchResult] -> [Item]
allItems sr = sr >>= searchResultItems -- using bind/flatMap for lists to concat all of these
-- | Function 2 -- Okay this is a bit gnarly. We are using a monadic list
-- unfold operation, to expand a whole list of search results out from an
-- initial seed search result. final list includes the initial search
-- result
unfoldSearch :: SearchResult -> Future [SearchResult]
unfoldSearch sr =
-- our unfolder operates from a Maybe Link down, so we have to stick
-- this search result on the front, and pass it's link in as the first
-- step in the recursion
fmap (sr :) (unfoldrM ourSearchUnfolder (searchResultNextLink sr))
-- The shape of this function is designed to match the first parameter to
-- unfoldrM
ourSearchUnfolder :: Maybe Link -- a
-> Future {- m -} (Maybe (SearchResult {- b -}, Maybe Link {- a -} ))
ourSearchUnfolder Nothing = return Nothing -- If we have nothing to do, we are done
ourSearchUnfolder (Just link) =
do nextSearchResult <- nextPage link
-- the first item in this pair goes into the output list
-- the second item goes is the seed for the next step of the loop
let result = (nextSearchResult, searchResultNextLink nextSearchResult)
return (Just result)
-- | stolen from monad-loops
unfoldrM :: (Monad m) => (a -> m (Maybe (b,a))) -> a -> m [b]
unfoldrM f = go
where go z = do
x <- f z
case x of
Nothing -> return []
Just (x, z') -> do
xs <- go z'
return ([x] ++ xs)
@nkpart
Copy link
Author

nkpart commented Jun 7, 2016

This may have been simpler if I ignored unfoldrM and just built the function with explicit recursion

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