How do you fmap a Getter? - haskell

As discussed on reddit, you can't just lift a Lens' a b to Lens' (Maybe a) (Maybe b). But for the special case Getter a b, this is obviously possible, since it's isomorphic to a->b. But unlike with Iso, there appears to be no standard function to perform this lift.
What's the preferred way to do that? In cases like
someFunction $ myMap^.at(i).ꜰᴍᴀᴘGᴇᴛ(mySubGetter)
I could of course do
someFunction $ myMap^.at(i) & fmap (^.mySubGetter)
but that doesn't work as well in other applications, as when operating on a state monad.
foo <- use $ myMapInState.at(i).ꜰᴍᴀᴘGᴇᴛ(mySubGetter)

I believe you can accomplish what you want with a prism.
If your values have these types:
myMap :: Map String (Int, String)
myMap = mempty
mySubGetter :: Lens' (Int, String) String
mySubGetter = _2
then you can do:
myVal :: Maybe String
myVal = myMap ^? at "myKey" . _Just . mySubGetter
If you just want to apply a function to a getter you can use the to function from Control.Lens.Getter, you have to manually deal with the sublens though:
someFunction $ myMap ^. at(i) . to (fmap (^. mySubGetter))

Related

How to convert a haskell List into a monadic function that uses list values for operations?

I am having trouble wrapping my head around making to work a conversion of a list into a monadic function that uses values of the list.
For example, I have a list [("dir1/content1", "1"), ("dir1/content11", "11"), ("dir2/content2", "2"), ("dir2/content21", "21")] that I want to be converted into a monadic function that is mapped to a following do statement:
do
mkBlob ("dir1/content1", "1")
mkBlob ("dir1/content11", "11")
mkBlob ("dir2/content2", "2")
mkBlob ("dir2/content21", "21")
I imagine it to be a function similar to this:
contentToTree [] = return
contentToTree (x:xs) = (mkBlob x) =<< (contentToTree xs)
But this does not work, failing with an error:
• Couldn't match expected type ‘() -> TreeT LgRepo m ()’
with actual type ‘TreeT LgRepo m ()’
• Possible cause: ‘(>>=)’ is applied to too many arguments
In the expression: (mkBlob x) >>= (contentToTree xs)
In an equation for ‘contentToTree’:
contentToTree (x : xs) = (mkBlob x) >>= (contentToTree xs)
• Relevant bindings include
contentToTree :: [(TreeFilePath, String)] -> () -> TreeT LgRepo m ()
I do not quite understand how to make it work.
Here is my relevant code:
import Data.Either
import Git
import Data.Map
import Conduit
import qualified Data.List as L
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy as BL
import Control.Monad (join)
type FileName = String
data Content = Content {
content :: Either (Map FileName Content) String
} deriving (Eq, Show)
contentToPaths :: String -> Content -> [(TreeFilePath, String)]
contentToPaths path (Content content) = case content of
Left m -> join $ L.map (\(k, v) -> (contentToPaths (if L.null path then k else path ++ "/" ++ k) v)) $ Data.Map.toList m
Right c -> [(BS.pack path, c)]
mkBlob :: MonadGit r m => (TreeFilePath, String) -> TreeT r m ()
mkBlob (path, content) = putBlob path
=<< lift (createBlob $ BlobStream $
sourceLazy $ BL.fromChunks [BS.pack content])
sampleContent = Content $ Left $ fromList [
("dir1", Content $ Left $ fromList [
("content1", Content $ Right "1"),
("content11", Content $ Right "11")
]),
("dir2", Content $ Left $ fromList [
("content2", Content $ Right "2"),
("content21", Content $ Right "21")
])
]
Would be grateful for any tips or help.
You have:
A list of values of some type a (in this case a ~ (String, String)). So, xs :: [a]
A function f from a to some type b in a monadic context, m b. Since you're ignoring the return value, we can imagine b ~ (). So, f :: Monad m => a -> m ().
You want to perform the operation, yielding some monadic context and an unimportant value, m (). So overall, we want some function doStuffWithList :: Monad m => [a] -> (a -> m ()) -> m (). We can search Hoogle for this type, and it yields some results. Unfortunately, as we've chosen to order the arguments, the first several results are little-used functions from other packages. If you scroll further, you start to find stuff in base - very promising. As it turns out, the function you are looking for is traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f (). With that, we can replace your do-block with just:
traverse_ mkBlob [ ("dir1/content1", "1")
, ("dir1/content11", "11")
, ("dir2/content2", "2")
, ("dir2/content21", "21")
]
As it happens there are many names for this function, some for historical reasons and some for stylistic reasons. mapM_, forM_, and for_ are all the same and all in base, so you could use any of these. But the M_ versions are out of favor these days because really you only need Applicative, not Monad; and the for versions take their arguments in an order that's convenient for lambdas but inconvenient for named functions. So, traverse_ is the one I'd suggest.
Assuming mkBlob is a function that looks like
mkBlob :: (String, String) -> M ()
where M is some specific monad, then you have the list
xs = [("dir1/content1", "1"), ("dir1/content11", "11"), ("dir2/content2", "2"), ("dir2/content21", "21")]
whose type is xs :: [(String, String)]. The first thing we need is to run the mkBlob function on each element, i.e. via map.
map mkBlob xs :: [M ()]
Now, we have a list of monadic actions, so we can use sequence to run them in sequence.
sequence (map mkBlob xs) :: M [()]
The resulting [()] value is all but useless, so we can use void to get rid of it
void . sequence . map mkBlob $ xs :: M ()
Now, void . sequence is called sequence_ in Haskell (since this pattern is fairly common), and sequence . map is called mapM. Putting the two together, the function you want is called mapM_.
mapM_ mkBlob xs :: M ()

What is a clean way of writing this function?

I would like some help with a problem I'm trying to solve. Let's say I have a type called Thing:
data Thing = ....
And I want to write a function that, given a string, tries to match it with some stuff in my state and return a Thing:
findFirstMatch :: String -> State (Maybe Thing)
The thing is, to match that string, it needs a list of possible strings to match it with. That list is provided by a function defined for my state:
getPossibilities :: State String
Now, I need to call a third function that receives the original string and one of the possibilities, and returns a Maybe Thing:
tryToMatch :: String -> String -> State (Maybe Thing)
How can I write findFirstMatch? I thought of doing this but it doesn't seem that clean, and it feels like there might be something already implemented:
findFirstMatch :: String -> State (Maybe Thing)
findFirstMatch str = do
xs <- getPossibilities
firstNotNull (map (tryToMatch str) xs)
firstNotNull :: [State (Maybe Thing)] -> State (Maybe Thing)
firstNotNull [] = return Nothing
firstNotNull (x:xs) = do
r <- x
case r of
Just _ -> return r
Nothing -> firstNotNull xs
First off, you can clean this up quite a bit if you write firstNotNull without using State. A very simple pass would be:
firstNotNull :: [Maybe Thing] -> Maybe Thing
firstNotNull [] = Nothing
firstNotNull (Just x:_) = Just x
firstNotNull Nothing:xs = firstNotNull xs
Furthermore, you can simplify even further by using some functions from Data.Maybe:
import Data.Maybe (catMaybes, listToMaybe)
firstNotNull :: [Maybe a] -> Maybe a
firstNotNull = listToMaybe . catMaybes
Now, let's turn our attention to findFirstMatch to see how we can use this simplified version of firstNotNull. The first question is: Does tryToMatch really need to live in State? After all, it already has access to both Strings that it's matching on. If you can change its type to tryToMatch :: String -> String -> Maybe Thing, then you're basically good to go.
On the other hand, if tryToMatch really does need to live in State, then there's just a little bit more to do: we need to pass firstNotNull a [Maybe Thing], but we have a [State (Maybe Thing)]. We can fix this by using sequenceA, as in:
findFirstMatch :: String -> State (Maybe Thing)
findFirstMatch str = do
xs <- getPossibilities
fmap firstNotNull $ sequenceA (map (tryToMatch str) xs)
Note that this only works if your State monad is lazy enough. If it's too strict, it will end up finding all matches, doing far too much work (and screwing up performance) and then return the first one.
From here, we can recognize that the usage of sequenceA and map can be reduced to a single call to traverse, as in:
fmap firstNotNull $ traverse (tryToMatch str) xs
This seems much cleaner!
Of course, we can still go further if we really want. It's not clear that the below changes actually make the code cleaner (rather, there's a strong argument that they make it harder to read), but let's have some fun anyway.
Rather than use do, we can choose to make this a one-liner with an appropriate use of monadic bind:
findFirstMatch str = getPossibilities $ \xs -> (fmap firstNotNull $ sequenceA (map (tryToMatch str) xs))
The inner lambda can be nicely eta-reduced to:
findFirstMatch str = getPossibilities >>= fmap firstNotNull . sequenceA . map (tryToMatch str)
And this too can be eta-reduced:
findFirstMatch = (getPossibilities >>=) . ((fmap firstNotNull . sequenceA) .) . map . tryToMatch
And while we're at it, why even have a definition of firstNotNull when we can inline it!
findFirstMatch :: String -> State (Maybe Thing)
findFirstMatch = (getPossibilities >>=) . ((fmap (listToMaybe . catMaybes) . sequenceA) .) . map . tryToMatch
There, your whole function in one messy line!

Efficiently search for a single element in a large Pandoc

Unless I'm missing something it seems that there are only two ways to "traverse" a Pandoc data-structure:
Manually pattern-matching on Block and Inline constructors
Via the Walkable type-class and related utility function
Using the Walkable type-class, is there an efficient way to search for the first matching element (preferably in a breadth-first manner), and stop the traversal as soon as its found? It seems to me that all functions around the Walkable type-class are going to traverse the entire data structure no matter what.
If not, I guess the only way is to pattern-match the Block and Inline constructors and build this on my own.
The other answer points out the useful query function. I'd add that there's a package of pandoc lenses. You asked about breadth-first traversal too, so here's both.
import Data.Semigroup (First (..))
dfsFirstLink :: Walkable Inline b => b -> Maybe Text
dfsFirstLink = fmap getFirst . query (preview $ _Link . _2 . _1 . to First)
bfsFirstLink :: Walkable Inline b => b -> Maybe Text
bfsFirstLink = fmap getFirst . getConst . traverseOf (levels query . folded) (Const . preview (_Link . _2 . _1 . to First))
-- Construct a walkable value where dfs != bfs
p :: Pandoc
p = Pandoc mempty [Plain [Note [Plain [Link mempty [] ("a","b")]]],Plain [Link mempty [] ("c","d")]]
>> dfsFirstLink p
Just "a"
>> bfsFirstLink p
Just "c"
Though unfortunately some ad-hoc experiments suggest it may not be as lazy as one might hope.
The Walkable typeclass contains a function called query with the following type signature:
query :: Monoid c => (a -> c) -> b -> c
In Data.Semigroup, there's a type called First, with a semigroup instance where the accumulating behavior is to return the "leftmost value".
This can be combined with the Monoid on Maybe, which turns any Semigroup into a Monoid with mempty of Nothing, to give the behavior you want.
For example, adapting a function from Inline -> Maybe String, to Pandoc -> Maybe String, can be done like so:
import Text.Pandoc
import Text.Pandoc.Walk (query)
import Data.Semigroup
findUrl :: Inline -> Maybe String
findUrl (Link _ _ target) = Just $ fst target
findUrl _ = Nothing
findFirstUrl :: Pandoc -> Maybe String
findFirstUrl = (fmap getFirst) . (query findUrl')
where
findUrl' :: Inline -> Maybe (First String)
findUrl' = (fmap First) . findUrl
With regards to your concern that this will traverse the entire data structure: Haskell is lazy; it shouldn't traverse any further than it needs to.
As pointed out in the comments, it's also possible to write this by specializing query to the List Monoid:
import Text.Pandoc
import Text.Pandoc.Walk (query)
import Data.Maybe (listToMaybe)
findUrl :: Inline -> [String]
findUrl (Link _ _ target) = [fst target]
findUrl _ = []
findFirstUrl :: Pandoc -> Maybe String
findFirstUrl = listToMaybe . (query findUrl)

Chaining functions of type IO (Maybe a )

I am writing a small library for interacting with a few external APIs. One set of functions will construct a valid request to the yahoo api and parse the result to a data type. Another set of functions will look up the users current location based on IP and return a data type representing the current location. While the code works, it seems having to explicitly pattern match to sequence multiple functions of type IO (Maybe a).
-- Yahoo API
constructQuery :: T.Text -> T.Text -> T.Text
constructQuery city state = "select astronomy, item.condition from weather.forecast" <>
" where woeid in (select woeid from geo.places(1)" <>
" where text=\"" <> city <> "," <> state <> "\")"
buildRequest :: T.Text -> IO ByteString
buildRequest yql = do
let root = "https://query.yahooapis.com/v1/public/yql"
datatable = "store://datatables.org/alltableswithkeys"
opts = defaults & param "q" .~ [yql]
& param "env" .~ [datatable]
& param "format" .~ ["json"]
r <- getWith opts root
return $ r ^. responseBody
run :: T.Text -> IO (Maybe Weather)
run yql = buildRequest yql >>= (\r -> return $ decode r :: IO (Maybe Weather))
-- IP Lookup
getLocation:: IO (Maybe IpResponse)
getLocation = do
r <- get "http://ipinfo.io/json"
let body = r ^. responseBody
return (decode body :: Maybe IpResponse)
-- Combinator
runMyLocation:: IO (Maybe Weather)
runMyLocation = do
r <- getLocation
case r of
Just ip -> getWeather ip
_ -> return Nothing
where getWeather = (run . (uncurry constructQuery) . (city &&& region))
Is it possible to thread getLocation and run together without resorting to explicit pattern matching to "get out" of the Maybe Monad?
You can happily nest do blocks that correspond to different monads, so it's just fine to have a block of type Maybe Weather in the middle of your IO (Maybe Weather) block.
For example,
runMyLocation :: IO (Maybe Weather)
runMyLocation = do
r <- getLocation
return $ do ip <- r; return (getWeather ip)
where
getWeather = run . (uncurry constructQuery) . (city &&& region)
This simple pattern do a <- r; return f a indicates that you don't need the monad instance for Maybe at all though - a simple fmap is enough
runMyLocation :: IO (Maybe Weather)
runMyLocation = do
r <- getLocation
return (fmap getWeather r)
where
getWeather = run . (uncurry constructQuery) . (city &&& region)
and now you see that the same pattern appears again, so you can write
runMyLocation :: IO (Maybe Weather)
runMyLocation = fmap (fmap getWeather) getLocation
where
getWeather = run . (uncurry constructQuery) . (city &&& region)
where the outer fmap is mapping over your IO action, and the inner fmap is mapping over your Maybe value.
I misinterpreted the type of getWeather (see comment below) such that you will end up with IO (Maybe (IO (Maybe Weather))) rather than IO (Maybe Weather).
What you need is a "join" through a two layer monad stack. This is essentially what a monad transformer provides for you (see #dfeuer's answer) but it is possible to write this combinator manually in the case of Maybe -
import Data.Maybe (maybe)
flatten :: (Monad m) => m (Maybe (m (Maybe a))) -> m (Maybe a)
flatten m = m >>= fromMaybe (return Nothing)
in which case you can write
runMyLocation :: IO (Maybe Weather)
runMyLocation = flatten $ fmap (fmap getWeather) getLocation
where
getWeather = run . (uncurry constructQuery) . (city &&& region)
which should have the correct type. If you are going to chain multiple functions like this, you will need multiple calls to flatten, in which case it maybe be easier to build a monad transformer stack instead (with the caveat's in #dfeuer's answer).
There is probably a canonical name for the function I've called "flatten" in the transformers or mtl libraries, but I can't find it at the moment.
Note that the function fromMaybe from Data.Maybe essentially does the case analysis for you, but abstracts it into a function.
Some consider this an anti-pattern, but you could use MaybeT IO a instead of IO (Maybe a). The problem is that you only deal with one of the ways getLocation can fail—it could also throw an IO exception. From that perspective, you might as well drop the Maybe and just throw your own exception if decoding fails, catching it wherever you like.
change getWeather to have Maybe IpResponse->IO.. and use >>= to implement it and then you can do getLocation >>= getWeather. The >>= in getWeather is the one from Maybe, that will deal with Just and Nothing and the other getLocation>>= getWeather the one from IO.
you can even abstract from Maybe and use any Monad: getWeather :: Monad m -> m IpResponse -> IO .. and will work.

How can I express `mapM` with `concat` using Lenses to concatenate results of an IO operation?

I'm trying to figure out a way how to combine traverseOf with >>= in such a way that would allow the following.
TLDR; A simple example in plain Haskell would be something like this, but using lenses deep inside a data structure.
λ> fmap concat $ mapM ((return :: a -> IO a) . const ["he", "he"]) ["foo", "bar", "baz"]
["he","he","he","he","he","he"]
Here's a lengthy explanation with examples
data Foo = Foo [Bar] deriving Show
data Bar = Baz | Qux Int [String] deriving Show
makePrisms ''Foo
makePrisms ''Bar
items :: [Foo]
items = [Foo [Baz], Foo [Qux 1 ["hello", "world"], Baz]]
-- Simple replacement with a constant value
constReplace :: [Foo]
constReplace = over (traverse._Foo.traverse._Qux._2.traverse) (const "hehe") items
-- λ> constReplace
-- [Foo [Baz],Foo [Qux 1 ["hehe","hehe"],Baz]]
-- Doing IO in order to fetch the new value. This could be replacing file names
-- with the String contents of the files.
ioReplace :: IO [Foo]
ioReplace = (traverse._Foo.traverse._Qux._2.traverse) (return . const "hehe") items
-- λ> ioReplace
-- [Foo [Baz],Foo [Qux 1 ["hehe","hehe"],Baz]]
-- Replacing a single value with a list and concatenating the results via bind
concatReplace :: [Foo]
concatReplace = over (traverse._Foo.traverse._Qux._2) (>>= const ["he", "he"]) items
-- λ> concatReplace
-- [Foo [Baz],Foo [Qux 1 ["he","he","he","he"],Baz]]
-- Same as the previous example, but the list comes from an IO action
concatIoReplace :: IO [Foo]
concatIoReplace = (traverse._Foo.traverse._Qux._2) (return . (>>= const ["he", "he"])) items
-- λ> concatIoReplace
-- [Foo [Baz],Foo [Qux 1 ["he","he","he","he"],Baz]]
Now the last example is where the problem is, because I've cheated a little bit by changing around the function that's being applied. In the concatReplace I was able to use >>= (thanks to the helpful guys on #haskell-lens channel) to implement the concatMap-like functionality. But in my real code the function I have is String -> IO [String], which would look something like this
correctConcatIo :: IO [Foo]
correctConcatIo = (traverse._Foo.traverse._Qux._2) (>>= (return . const ["he", "he"])) items
But this example doesn't typecheck anymore. What I need is to basically put together the logic from ioReplace and concatReplace in a way that I would be able to apply a function with the type String -> IO [String] to a data structure containing [String].
You can only replace a String with [String] if it's already in a list (consider trying to stick a [Int] back into _Qux._1), so you have to turn your function into [String]->IO [String] and replace the whole list, using some approach like you've already demonstrated:
concatMapM f l = fmap concat (mapM f l)
doIOStuff s = return ['a':s, 'b':s]
concatIO :: IO [Foo]
concatIO = (traverse._Foo.traverse._Qux._2) (concatMapM doIOStuff) items
You can even compose that concatMapM onto the end to get something with a LensLike type, but it's not flexible enough to use with most of the lens combinators.

Resources