beam icon indicating copy to clipboard operation
beam copied to clipboard

LensFor: `Couldn't match expected type p`

Open yaitskov opened this issue 2 years ago • 7 comments

After upgrading GHC version from 8.10.7 to 9.2.4 following snippets fails:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -fplugin=Polysemy.Plugin #-}

module Foo where

data Foo f = Foo  { fooInt :: C f Int }  deriving (Generic, Beamable)

module Bar where
{-# LANGUAGE ImpredicativeTypes #-}
{-# OPTIONS_GHC -Wno-missing-signatures #-}

import Database.Beam (LensFor (LensFor), TableLens (TableLens), dbLenses, tableLenses)
import Foo

Foo  (LensFor x)  = tableLenses

Couldn't match expected type ‘p’
              with actual type ‘microlens-0.4.12.0:Lens.Micro.Type.Lens'
                                  (Foo f1)
                                  (Database.Beam.Schema.Tables.Columnar
                                     f1 ghc-prim-0.8.0:GHC.Types.Int)’
  Cannot equate type variable ‘p’
  with a type involving polytypes:
    microlens-0.4.12.0:Lens.Micro.Type.Lens'
      (Foo f1)
      (Database.Beam.Schema.Tables.Columnar
         f1 ghc-prim-0.8.0:GHC.Types.Int)
  ‘p’ is a rigid type variable bound by
    the inferred type of x :: p
    at /home/dan/pro/Bar.hs:10:1-29
• In the pattern: LensFor x
  In the pattern: Foo (LensFor x)
  In a pattern binding: Foo (LensFor x) = tableLensestypecheck(-Wdeferred-type-errors)

yaitskov avatar Jan 12 '23 14:01 yaitskov

I figured out how to define lenses manually as a workaround:

fooName ::
  forall (f1 :: Type -> Type) (f2 :: Type -> Type).
  Functor f2 =>
  (Columnar f1 Text -> f2 (Columnar f1 Text)) -> FooT f1 -> f2 (FooT f1)
fooName fa u = (\x -> u { _name = x } ) <$> fa (_name u)

yaitskov avatar Jan 12 '23 18:01 yaitskov

I have also seen this here which uses GHC 9.2: https://github.com/haskell-beam/beam/pull/650 The errors can be seen with nix-build release.nix


@gelisam helpfully directed me to look more closely at the ImpredicativeTypes extension.

The snippets rely on it: https://github.com/haskell-beam/beam/blob/94461937c5ca8b89f1ff1a60bde5bffe207315b4/docs/tutorials/tutorial2.md?plain=1#L237-L240

This says ImpredicativeTypes was unreliable before GHC 9.2: https://ghc.gitlab.haskell.org/ghc/doc/users_guide/exts/impredicative_types.html Now perhaps the extension has changed?

peterbecich avatar Jan 15 '23 21:01 peterbecich

I hit the same issue at 9.2.7. Writing the type signature by hand still (with NoMonomorphismRestriction enabled) doesn't work. I tried fooName :: forall f. Functor f => Lens' (FooT f) (C f Text), though it compiles, but at the use site there is an error No instance for (Functor ...). I also tried expanding Lens' further: fooName :: forall f1 f2. Functor f2 => (C f1 Text -> f2 (C f1 Text)) -> FooT f1 -> f2 (FooT f1), but this doesn't compile due to Could not deduce (Functor f1) arising from GHC Bug #20076.

berberman avatar Mar 22 '23 02:03 berberman

@berberman and @yaitskov

Have you tried


Module Foo where 

import Database.Beam 
import Lens.Micro 

data FooT f = Foo  { _fooInt :: C f Int }  deriving (Generic, Beamable)
type Foo = FooT Identity 

fooName :: Lens Foo Foo Int Int 
Foo  (LensFor fooName)  = tableLenses

arguri avatar Mar 24 '23 10:03 arguri

@arguri, it only works for data with 1 field (i.e. newtype)

• Could not deduce (Functor f0) arising from GHC Bug #20076
  from the context: Functor f
    bound by the inferred type for ‘projectName’:
               Lens HackageProject HackageProject Text Text
    at /home/dan/pro/Tables/HackageProject.hs:42:1-71
  The type variable ‘f0’ is ambiguous
  These potential instances exist:
    instance Functor (Either a) -- Defined in ‘Data.Either’
    instance Functor Identity -- Defined in ‘Data.Functor.Identity’
    instance Functor (With be db)
      -- Defined in ‘Database.Beam.Query.CTE’
    ...plus 9 others
    ...plus 281 instances involving out-of-scope types
    (use -fprint-potential-instances to see them all)
• When checking that the inferred type
    projectName :: forall {f1 :: * -> *} {f2 :: * -> *}.
                   (Functor f1, Functor f2) =>
                   (Text -> f1 Text) -> HackageProject -> f1 HackageProject
  is as general as its signature
    projectName :: Lens HackageProject HackageProject Text Text

yaitskov avatar Apr 11 '23 18:04 yaitskov

@yaitskov

For more fields you would need to add Signatures for each field and ignore the other fields, e.g.

module Foo where 

import Database.Beam 
import Lens.Micro 

data Foo { fooName :: C f Int, fooId :: C f String } deriving (Generic, Beamable)

fooName :: Lens Foo Foo Int Int 
fooId :: Lens Foo Foo String String 
Foo (LensFor fooName) _ = tableLenses 
Foo _ (LensFor fooId) = tableLenses 

At least that worked for me.

arguri avatar Apr 15 '23 07:04 arguri

Thanks, I see - every lens binding should have dedicated expression and they cannot be batched in one data constructor.

yaitskov avatar May 06 '23 13:05 yaitskov