[Haskell-cafe] About using "type" to do type alias.

Magicloud Magiclouds magicloud.magiclouds at gmail.com
Mon Jun 25 11:19:03 CEST 2012


Sorry, I forgot that. Magicloud.Map.mapM sure is a helper I use as
lifted Data.Map.map.
If I changed the type of the result of start, the Jobs module
compiled. But still cannot compile with the other module (which uses
start). And the error is on JobArgs.
I post the function here, I am not sure how could I fix it.

mapM :: (Monad m, Ord k) => (a -> m b) -> M.Map k a -> m (M.Map k b)
mapM f m =
  let (ks, as) = unzip $ M.toList m
  in
    Prelude.mapM f as >>=
      return . M.fromList . zip ks

On Mon, Jun 25, 2012 at 5:11 PM, Ivan Lazar Miljenovic
<ivan.miljenovic at gmail.com> wrote:
> On 25 June 2012 19:04, Arlen Cuss <ar at len.me> wrote:
>> Magicloud,
>>
>> Try to reduce the particular problem you're having to the smallest possible example that reproduces the issue. None of us can compile your code, either, because we're missing many of the dependencies, and unfortunately the issue is no easier (for me) to track down with the full source listing in this case.
>
> Though line 22 reveals something: I don't know what Magicloud.Map.mapM
> is, though I'm guessing it's a lifted version of Data.Map.map.
> However, I would guess that it's a type problem.
>
> Try changing the type of start to be ` start :: (Ord k, Exception e)
> => JobArgs k a -> (a -> IO b) -> IO (M.Map k (JobInfo a e)) '; I would
> hazard a guess that you would get the same error, and thus the problem
> isn't with `type', it's that your mapping function isn't quite
> correct.
>
>>
>> Cheers,
>>
>> Arlen
>>
>>
>> On Monday, 25 June 2012 at 5:46 PM, Magicloud Magiclouds wrote:
>>
>>> Here is the code, I joined two modules in one paste. Both of them
>>> cannot pass compiling.
>>>
>>> http://hpaste.org/70418
>>>
>>> On Mon, Jun 25, 2012 at 2:16 PM, Ivan Lazar Miljenovic
>>> <ivan.miljenovic at gmail.com (mailto:ivan.miljenovic at gmail.com)> wrote:
>>> > On 25 June 2012 12:50, Magicloud Magiclouds
>>> > <magicloud.magiclouds at gmail.com (mailto:magicloud.magiclouds at gmail.com)> wrote:
>>> > > Hi,
>>> > > There was another mail, but the subject might be confusing. So I
>>> > > write this one. The code is here: http://hpaste.org/70414
>>> > > If I understand correct, generally, I could use 'type' to do alias
>>> > > to save the ugly-long code. Like section 1. This works when I 't [(0,
>>> > > Just "x")]'.
>>> > >
>>> > > But, if I wrote section 2. Then 'start (M.fromList $ zip ord_args)
>>> > > worker' could not be compiled due to the second argument is type of
>>> > > 'M.Map Arg Arg', not 'JobArgs Arg Arg'.
>>> >
>>> >
>>> >
>>> > This shouldn't make a difference. As an example, this works:
>>> >
>>> > > import qualified Data.Map as M
>>> > >
>>> > > type Foo a b = M.Map a b
>>> > >
>>> > > fooInsert :: (Ord a) => a -> b -> Foo a b -> Foo a b
>>> > > fooInsert = M.insert
>>> >
>>> >
>>> >
>>> > Aliases are just for documentation; they shouldn't affect code working.
>>> >
>>> >
>>> > >
>>> > > What did I miss to make this work?
>>> > > --
>>> > > 竹密岂妨流水过
>>> > > 山高哪阻野云飞
>>> > >
>>> > > And for G+, please use magiclouds#gmail.com (http://gmail.com).
>>> > >
>>> > > _______________________________________________
>>> > > Haskell-Cafe mailing list
>>> > > Haskell-Cafe at haskell.org (mailto:Haskell-Cafe at haskell.org)
>>> > > http://www.haskell.org/mailman/listinfo/haskell-cafe
>>> >
>>> >
>>> >
>>> >
>>> >
>>> > --
>>> > Ivan Lazar Miljenovic
>>> > Ivan.Miljenovic at gmail.com (mailto:Ivan.Miljenovic at gmail.com)
>>> > http://IvanMiljenovic.wordpress.com
>>>
>>>
>>>
>>>
>>>
>>> --
>>> 竹密岂妨流水过
>>> 山高哪阻野云飞
>>>
>>> And for G+, please use magiclouds#gmail.com (http://gmail.com).
>>>
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe at haskell.org (mailto:Haskell-Cafe at haskell.org)
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>>
>
>
>
> --
> Ivan Lazar Miljenovic
> Ivan.Miljenovic at gmail.com
> http://IvanMiljenovic.wordpress.com



-- 
竹密岂妨流水过
山高哪阻野云飞

And for G+, please use magiclouds#gmail.com.



More information about the Haskell-Cafe mailing list