[Haskell-cafe] Selda: confused about type signtures

Marc Busqué marc at lamarciana.com
Fri Apr 20 18:46:30 UTC 2018


On Fri, 20 Apr 2018, Tom Ellis wrote:

> Did you try applying the suggested fix?  Explicitly, add
>
> {-# LANGUAGE FlexibleContexts #-}
>
> at the top of your file to permit this.

It doesn't work neither. In this case the error is:

```
• Couldn't match type ‘selda-0.1.12.1:Database.Selda.Compile.Res
                          (selda-0.1.12.1:Database.Selda.Column.Cols s0 a)’
                  with ‘selda-0.1.12.1:Database.Selda.Compile.Res
                          (selda-0.1.12.1:Database.Selda.Column.Cols s a)’
   Expected type: Table a
                  -> IO
                       [selda-0.1.12.1:Database.Selda.Compile.Res
                          (selda-0.1.12.1:Database.Selda.Column.Cols s a)]
     Actual type: Table a
                  -> IO
                       [selda-0.1.12.1:Database.Selda.Compile.Res
                          (selda-0.1.12.1:Database.Selda.Column.Cols s0 a)]
   NB: ‘selda-0.1.12.1:Database.Selda.Compile.Res’ is a type function, and may not be injective
   The type variable ‘s0’ is ambiguous
• In the ambiguity check for the inferred type for ‘list’
   To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
   When checking the inferred type
     list :: forall s a.
             (selda-0.1.12.1:Database.Selda.Column.Columns
                (selda-0.1.12.1:Database.Selda.Column.Cols s a),
              selda-0.1.12.1:Database.Selda.Compile.Result
                (selda-0.1.12.1:Database.Selda.Column.Cols s a)) =>
             Table a
             -> IO
                  [selda-0.1.12.1:Database.Selda.Compile.Res
                     (selda-0.1.12.1:Database.Selda.Column.Cols s a)]
    |
36 | list table = withDB $ query (select table)
```

Anyway, I'm more interested in understanding an explicit type signature,
in this case.

Marc Busqué
http://waiting-for-dev.github.io/about/


More information about the Haskell-Cafe mailing list