[Haskell-cafe] Typeable state map

Vladimir Matveev dpx.infinity at gmail.com
Wed Nov 10 16:47:48 EST 2010


Thank you, that was exactly what I needed. Now program compiles flawlessly.

2010/11/10 Neil Brown <nccb2 at kent.ac.uk>:
> Hi,
>
> You have a problem with your function getPhi.  It has type:
>
> getPhi :: forall a e m. (MutableMatrix a e m, Typeable a, Typeable e,
> Floating e, Ord e) => VarStateT m ()
>
> where MutableMatrix is:
>
> class (PrimMonad m) => MutableMatrix a e m | a -> e m where
>
> No matter how you call getPhi, you can't specify the 'a' and 'e' types --
> they don't appear in the real part of the type signature, and the fundep on
> the MutableMatrix class is not sufficient to determine 'a' or 'e' from 'm'.
>  This means that there is no way for the compiler to pick a type for 'a' or
> 'e' when getPhi is called, and there is no way to make the 'a' and 'e' for
> getPhi be the same as the 'a' and 'e' for compute.  getPhi needs to know
> what type it is attempting to cast the dynamic state into and at the moment
> you can't tell it.
>
> The solutions that I can think of are either to pass dummy parameters of
> type 'a' and 'e' to allow you to specify the type, or to add a fundep like m
> -> a e (but I don't think that one holds?).
>
> Thanks,
>
> Neil.
>
> On 10/11/10 13:10, Vladimir Matveev wrote:
>>
>> Hi,
>> I want to use something like (Control.Monad.StateT (Data.Map.Map
>> String Dynamic) m). So I wrote VarStateT datatype and corresponding
>> classes (Control/Monad/VarState.hs in [1]). Then I tried to use it in
>> my program (Math/Eigenvalues.hs in [1]). But compiler refused to
>> compile it with many type errors. I thought that it would be
>> sufficient to use ScopedTypeVariables and write all type annotations.
>> It helped slightly, many messages were gone, but now compiler throws
>> an error I don't know how to solve.
>>
>> ghc --make  -o out/eigenvalues -outputdir build Main.hs
>> [3 of 4] Compiling Math.Eigenvalues ( Math/Eigenvalues.hs,
>> build/Math/Eigenvalues.o )
>>
>> Math/Eigenvalues.hs:14:30:
>>     Could not deduce (MutableMatrix a e m)
>>       from the context (MutableMatrix a2 e2 m,
>>                         Typeable a2,
>>                         Typeable e2,
>>                         Floating e2,
>>                         Ord e2)
>>       arising from a use of `getPhi' at Math/Eigenvalues.hs:14:30-35
>>     Possible fix:
>>       add (MutableMatrix a e m) to the context of
>>         the type signature for `compute'
>>     In the second argument of `(>>)', namely `getPhi'
>>     In the first argument of `(>>)', namely `maxElem a>>  getPhi'
>>     In the first argument of `(>>)', namely
>>         `maxElem a>>  getPhi>>  buildB'
>>
>> Math/Eigenvalues.hs:14:40:
>>     Could not deduce (MutableMatrix a1 e1 m)
>>       from the context (MutableMatrix a2 e2 m,
>>                         Typeable a2,
>>                         Typeable e2,
>>                         Floating e2,
>>                         Ord e2)
>>       arising from a use of `buildB' at Math/Eigenvalues.hs:14:40-45
>>     Possible fix:
>>       add (MutableMatrix a1 e1 m) to the context of
>>         the type signature for `compute'
>>     In the second argument of `(>>)', namely `buildB'
>>     In the first argument of `(>>)', namely
>>         `maxElem a>>  getPhi>>  buildB'
>>     In the first argument of `(>>=)', namely
>>         `maxElem a>>  getPhi>>  buildB>>  buildA'
>>
>> How to sort this out?
>>
>> [1] http://dl.dropbox.com/u/1415321/prog/eigenvalues.tar.gz
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>


More information about the Haskell-Cafe mailing list