Hi Amit!

I was initially a little confused by having both a `tr` type variable and a `r` type variable.  Pretty sure that's a typo and they're intended to be the same.  Otherwise you'd need to pass in something like `Proxy r` so that the usage of saveToDb constrains all the type variables.

ClassyPrelude has a good solution to this problem, where you want to constrain the type of the container but not explicitly describe its contents.  Check out this section: https://hackage.haskell.org/package/classy-prelude-0.12.4/docs/ClassyPrelude.html#g:27

In this case, you'd use "asList":

asList :: [a] -> [a]
asList = id

And then use this like so: `forM_ (asList rows) processRow`

Alternatively, I think this will work if you enable PartialTypeSignatures (new in 7.10): `forM_ (rows :: [_]) processRow`

-Michael

On Thu, Oct 15, 2015 at 1:17 PM, Amit Aryeh Levy <amit@amitlevy.com> wrote:
Thanks Adam!

Vector does make more sense (i'll continue to use lists in this thread
just for simplicity, since I don't think it matters for the higher level
problem).

`forM_ (objs :: Type) ....` seems like exactly the right solution in the
simple case. However, it doesn't seem to work if I try to write a more
general function. For example:

```
class ToRow r

saveToDb :: FromJSON r, ToRow r => ByteString -> (tr -> IO ()) -> IO ()
saveToDb json processRow =
    case eitherDecode json of
        Left err => return () -- for simplicity
        Right rows => forM_ (rows :: [r]) processRow
```

GHC complains about two things:

    1. eitherDecode can't determine which `FromJSON` instance to use
    2. "Couldn't match expected type [r1] with actual type a0" in `rows
:: [r]`.

I think the issue is that GHC is not relating `rows :: [r]` to `FromJSON
r` in the function type.

Falling back to either ScopedTypeVariables or explicit
contruction/deconstruction of the list works:

```
class ToRow r

saveToDb :: FromJSON r, ToRow r => ByteString -> (tr -> IO ()) -> IO ()
saveToDb json processRow =
    case eitherDecode json of
        Left err => return () -- for simplicity
        Right (rows :: [r]) => forM_ rows processRow
```

Thoughts?

Thanks!
Amit

P.S.
Thanks to Felipe for politely reminding me that these are lists we are
dealing with, not arrays!

On 10/15/2015 02:27 PM, Adam Bergmark wrote:
> If you care about performance you may - I haven't benchmarked - want to use
> Vector instead of lists here since that's what aeson uses internally. Then
> it's pretty handy that you can still use forM_.
>
> It's possible that the list pattern deconstruction and list construction
> gets optimized away, my gut says you need -O2 for that to happen. Here's a
> good explanation on how to dump and read core so you can check for yourself
> what happens in this case:
> http://stackoverflow.com/questions/6121146/reading-ghc-core . Either way
> it's definitiely not less efficient to annotate the type instead. You don't
> need ScopedTypeVariables here, you can write the type inside an expression
> instead: `forM (objs :: Type) [...]`
>
> HTH,
> Adam
>
>
> On Thu, Oct 15, 2015 at 7:16 PM, Amit Aryeh Levy <amit@amitlevy.com> wrote:
>
>> I've been running into a relatively small but frequent annoyance with
>> base >= 4.8 (GHC 7.10). `Control.Monad.foldM_`, `Control.Monad.mapM_`
>> and `Control.Monad.forM_` are generalized traverse over any `Foldable a`
>> rather than just arrays (`[a]`).
>>
>>  This is great, except I'm finding that, for a lot of my code that works
>> well in previous versions, I need to specialize the argument to `[a]`
>> now. If other people are encoutering a similar patter, I wonder what are
>> your best practices for doing this: ScopedTypeVariables? Deconstruct the
>> reconstruct the array? ...
>>
>>  The most common example is when I deserialize a JSON array with aeson
>> and want to traverse over that array (say, to store the objects to a DB):
>>
>>  ```
>> let objArray = eitherDecode myjson
>> case objArray of
>>     Left err -> ...
>>     Right (objs :: [MyObjType]) ->
>>         forM_ objs $ \obj -> saveToDb obj
>>  ```
>>
>> ​The above fix requires `ScopedTypeVariables` (which is probably OK).
>> Another option is to deconstruct and reconstruct the list:
>>
>> ```
>> Right (o:objs) ->
>>     forM_ (o:objs) $ \obj -> saveToDb obj
>> ```
>>
>> Does this get optimized away?
>>
>> Penny for your thoughts?
>>
>> Cheers!
>> Amit
>>
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>>
>>



_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe