[Haskell-cafe] Selda: confused about type signtures
Marc Busqué
marc at lamarciana.com
Tue Apr 24 06:00:32 UTC 2018
Just for completeness about this solution:
On Mon, 23 Apr 2018, Li-yao Xia wrote:
> ```
> {-# LANGUAGE AllowAmbiguousTypes #-}
> {-# LANGUAGE ScopedTypeVariables #-}
>
> list :: forall s a. (Result (Cols s a), Columns (Cols s a))
> => Table a -> IO [Res (Cols s a)]
> list table = withDB $ query (select table :: Query s _)
This gives error:
```
• Couldn't match type ‘Res a’ with ‘Res (Cols s a)’
Expected type: IO [Res (Cols s a)]
Actual type: IO [Res a]
NB: ‘Res’ is a type function, and may not be injective
• In the expression: withDB $ query (select table :: Query s a)
In an equation for ‘list’:
list table = withDB $ query (select table :: Query s a)
• Relevant bindings include
table :: Table a (bound at src/Hedger/Backend.hs:30:6)
list :: Table a -> IO [Res (Cols s a)]
(bound at src/Hedger/Backend.hs:30:1)
|
30 | list table = withDB $ query (select table :: Query s a)
Couldn't match type ‘a’ with ‘Cols s a’
‘a’ is a rigid type variable bound by
the type signature for:
list :: forall s a.
(Result (Cols s a), Columns (Cols s a)) =>
Table a -> IO [Res (Cols s a)]
at src/Hedger/Backend.hs:29:1-93
Expected type: Query s a
Actual type: Query s (Cols s a)
• In the first argument of ‘query’, namely
‘(select table :: Query s a)’
In the second argument of ‘($)’, namely
‘query (select table :: Query s a)’
In the expression: withDB $ query (select table :: Query s a)
• Relevant bindings include
table :: Table a (bound at src/Hedger/Backend.hs:30:6)
list :: Table a -> IO [Res (Cols s a)]
(bound at src/Hedger/Backend.hs:30:1)
|
30 | list table = withDB $ query (select table :: Query s a)
```
> -- or, ... (select @s table)
> -- with {-# LANGUAGE TypeApplications #-}
> ```
This indeed works!!
In either case, however, I need to add `{-# LANGUAGE FlexibleContexts #-}`
Now I have an interesting road in front of me in order to try to
understand it, along with Tom Ellis' isolated reproducing environment :)
Marc Busqué
http://waiting-for-dev.github.io/about/
More information about the Haskell-Cafe
mailing list