[Haskell-beginners] Ambiguous type of WriterT result I am not using

David McBride toad3k at gmail.com
Fri Nov 20 15:46:38 UTC 2015


The problem is in your string -> WriterT w m a.  It needs to know what the
w is.  It knows its a monoid but doesn't know anything else about it.  The
simplest thing is to just tell it what it is.

foldrEntries :: (Entry -> a -> a) -> a -> (String -> a) -> Entries -> a
foldrEntries next done fail' es = runIdentity $ return . fst =<< runWriterT
foldIt
  where
    foldIt = foldrEntriesW (\e -> return . next e) (return done) ((return
:: Monad m => a -> WriterT () m a) . fail') es

A second option is to give foldIt a type signature.  Unfortunately if you
want the a in foldIt to match the a in foldEntries, you have to use scoped
type variables extension.  Normally the two signatures are not related and
the compiler figures both a's are not the same as each other.

{-# LANGUAGE ScopedTypeVariables #-}

...

foldrEntries :: forall a. (Entry -> a -> a) -> a -> (String -> a) ->
Entries -> a
foldrEntries next done fail' es = runIdentity $ return . fst =<< runWriterT
foldIt
  where
    foldIt :: Monad m => WriterT () m a
    foldIt = foldrEntriesW (\e -> return . next e) (return done) (return .
fail') es


On Fri, Nov 20, 2015 at 7:14 AM, Martin Vlk <martin at vlkk.cz> wrote:

> Hi I have two functions, foldrEntries and foldrEntriesW, where the
> latter is a WriterT version of the former. Here are the type signatures:
>
> foldrEntries :: (Entry -> a -> a) ->
>                 a ->
>                 (String -> a) ->
>                 Entries ->
>                 a
>
> foldrEntriesW :: (Monoid w, Monad m) =>
>                  (Entry -> a -> WriterT w m a) ->
>                  WriterT w m a ->
>                  (String -> WriterT w m a) ->
>                  Entries ->
>                  WriterT w m a
>
> I want to implement foldrEntries in terms of foldrEntriesW using the
> Identity monad and ignore/not use the writer result. I am doing this in
> order to reuse the foldrEntriesW implementation and avoid code duplication.
>
> This is what I have so far:
> http://lpaste.net/145641
>
> But the compiler complains about ambiguous type for the writer reult I
> am ignoring (message in the above lpaste).
>
> Normally I think the way around this is to provide explicit type
> annotation for "foldIt", but in this case the result type depends on the
> type of "a" in foldrEntries type and I don't know how to express this
> and make the compiler happy.
>
> (I was able to make it work by calling "tell ()", basically writing a
> dummy value, which lets compiler know what the type is, but this is not
> so good - I don't want to make artificial function calls like this.)
>
> Can anybody help me with that?
>
> Many Thanks
> Martin
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/beginners/attachments/20151120/dacb4324/attachment.html>


More information about the Beginners mailing list