I haven't tested this out, but have you tried putting a functional dependency on the class(| a -> b)? Could also put each method in its own class.
--
Sent from my phone with K-9 Mail.


On 18 August 2022 04:37:47 UTC, Henry Laxen <nadine.and.henry@pobox.com> wrote:
-- run this with:  ghci -package microlens-platform T7.hs
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE FlexibleInstances #-}

module T7 where

import Lens.Micro.Platform

type Lenstype f a b = (b -> f b) -> a -> f a

data A = A { _a1 :: Int , _a2 :: String} deriving (Show)
$(makeLenses ''A)

class B a where
lensB1 :: (Functor f) => Lenstype f a Int
lensB2 :: (Functor f) => Lenstype f a String

instance B A where
lensB1 = a1
lensB2 = a2

xa = A 1 "one"
ya1 = xa ^. a1
ya2 = xa ^. lensB1

test1 = ya1 == ya2 -- True

-- But I would like to use a type variable for the String field of A

data C b = C { _c1 :: Int , _c2 :: b} deriving (Show)
$(makeLenses ''C)

-- So next I define:

class D a b where -- Need MultiParamTypeClasses here
lensD1 :: (Functor f) => Lenstype f a Int -- Need AllowAmbiguousTypes here
lensD2 :: (Functor f) => Lenstype f a b

instance D (C b) b where -- Need FlexibleInstances here
lensD1 = c1
lensD2 = c2

xc1 = C 1 "one" :: C String
xc2 = C 1 'o' :: C Char

yc1 = xc1 ^. c1 :: Int
yc2 = xc2 ^. c1 :: Int

test2 = yc1 == yc2 -- True

-- All good until here. Now the trouble begins. If you uncomment the next two lines you get:

-- zc1 = xc1 ^. lensD1 :: Int
-- zc2 = xc2 ^. lensD1 :: Int

-- T7.hs:62:14-19: error:
-- • Ambiguous type variable ‘b1’ arising from a use of ‘lensD1’
-- prevents the constraint ‘(D (C String) b1)’ from being solved.
-- Probable fix: use a type annotation to specify what ‘b1’ should be.
-- These potential instance exist:
-- instance D (C b) b
-- -- Defined at /home/henry/haskell/dev/T7.hs:44:10
-- • In the second argument of ‘(^.)’, namely ‘lensD1’
-- In the expression: xc1 ^. lensD1 :: Int
-- In an equation for ‘zc1’: zc1 = xc1 ^. lensD1 :: Int
-- |
-- 62 | zc1 = xc1 ^. lensD1 :: Int
-- | ^^^^^^

-- T7.hs:63:14-19: error:
-- • Ambiguous type variable ‘b0’ arising from a use of ‘lensD1’
-- prevents the constraint ‘(D (C Char) b0)’ from being solved.
-- Probable fix: use a type annotation to specify what ‘b0’ should be.
-- These potential instance exist:
-- instance D (C b) b
-- -- Defined at /home/henry/haskell/dev/T7.hs:44:10
-- • In the second argument of ‘(^.)’, namely ‘lensD1’
-- In the expression: xc2 ^. lensD1 :: Int
-- In an equation for ‘zc2’: zc2 = xc2 ^. lensD1 :: Int
-- |
-- 63 | zc2 = xc2 ^. lensD1 :: Int
-- | ^^^^^^


-- But zc1 and zc2 don't care what is in the second slot. I would
-- like to store different types in the second slot of C, but the
-- first slot of C will always be an Int. Is there any way to
-- manipulate the first slot alone? I got some compiler "suggestions"
-- concernting RankNTypes and QuantifiedConstraints but nothing I
-- tried ended up working.

-- Thanks in advance for your help.
-- Henry Laxen
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.