<html><head></head><body>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.<div style='white-space: pre-wrap'>--<br>Sent from my phone with K-9 Mail.</div><br><br><div class="gmail_quote">On 18 August 2022 04:37:47 UTC, Henry Laxen <nadine.and.henry@pobox.com> wrote:<blockquote class="gmail_quote" style="margin: 0pt 0pt 0pt 0.8ex; border-left: 1px solid rgb(204, 204, 204); padding-left: 1ex;">
<pre dir="auto" class="k9mail">-- run this with:  ghci -package microlens-platform T7.hs<br>{-# LANGUAGE TemplateHaskell #-}<br>{-# LANGUAGE TypeFamilies #-}<br>{-# LANGUAGE MultiParamTypeClasses #-}<br>{-# LANGUAGE AllowAmbiguousTypes #-}<br>{-# LANGUAGE FlexibleInstances #-}<br><br>module T7 where<br><br>import           Lens.Micro.Platform<br><br>type Lenstype f a b = (b -> f b) -> a -> f a<br><br>data A  = A { _a1 :: Int , _a2 :: String} deriving (Show)<br>$(makeLenses ''A)<br><br>class B a where<br>  lensB1 :: (Functor f) =>  Lenstype f a Int<br>  lensB2 :: (Functor f) =>  Lenstype f a String<br><br>instance B A where<br>  lensB1 = a1<br>  lensB2 = a2<br><br>xa  = A 1 "one"<br>ya1 = xa ^. a1<br>ya2 = xa ^. lensB1<br><br>test1 = ya1 == ya2  -- True<br><br>-- But I would like to use a type variable for the String field of A<br><br>data C b = C { _c1 :: Int , _c2 :: b} deriving (Show)<br>$(makeLenses ''C)<br><br>-- So next I define:<br><br>class D a b where                             -- Need MultiParamTypeClasses here<br>  lensD1 :: (Functor f) =>  Lenstype f a Int  -- Need AllowAmbiguousTypes here<br>  lensD2 :: (Functor f) =>  Lenstype f a b<br><br>instance D (C b) b where                      -- Need FlexibleInstances here<br>  lensD1 = c1<br>  lensD2 = c2<br><br>xc1 = C 1 "one"  :: C String<br>xc2 = C 1 'o'    :: C Char<br><br>yc1 = xc1 ^. c1  :: Int<br>yc2 = xc2 ^. c1  :: Int<br><br>test2 = yc1 == yc2 -- True<br><br>-- All good until here. Now the trouble begins.  If you uncomment the next two lines you get:<br><br>-- zc1 = xc1 ^. lensD1 :: Int<br>-- zc2 = xc2 ^. lensD1 :: Int<br><br>-- T7.hs:62:14-19: error:<br>--     • Ambiguous type variable ‘b1’ arising from a use of ‘lensD1’<br>--       prevents the constraint ‘(D (C String) b1)’ from being solved.<br>--       Probable fix: use a type annotation to specify what ‘b1’ should be.<br>--       These potential instance exist:<br>--         instance D (C b) b<br>--           -- Defined at /home/henry/haskell/dev/T7.hs:44:10<br>--     • In the second argument of ‘(^.)’, namely ‘lensD1’<br>--       In the expression: xc1 ^. lensD1 :: Int<br>--       In an equation for ‘zc1’: zc1 = xc1 ^. lensD1 :: Int<br>--    |<br>-- 62 | zc1 = xc1 ^. lensD1 :: Int<br>--    |              ^^^^^^<br><br>-- T7.hs:63:14-19: error:<br>--     • Ambiguous type variable ‘b0’ arising from a use of ‘lensD1’<br>--       prevents the constraint ‘(D (C Char) b0)’ from being solved.<br>--       Probable fix: use a type annotation to specify what ‘b0’ should be.<br>--       These potential instance exist:<br>--         instance D (C b) b<br>--           -- Defined at /home/henry/haskell/dev/T7.hs:44:10<br>--     • In the second argument of ‘(^.)’, namely ‘lensD1’<br>--       In the expression: xc2 ^. lensD1 :: Int<br>--       In an equation for ‘zc2’: zc2 = xc2 ^. lensD1 :: Int<br>--    |<br>-- 63 | zc2 = xc2 ^. lensD1 :: Int<br>--    |              ^^^^^^<br><br><br>-- But zc1 and zc2 don't care what is in the second slot.  I would<br>-- like to store different types in the second slot of C, but the<br>-- first slot of C will always be an Int.  Is there any way to<br>-- manipulate the first slot alone?  I got some compiler "suggestions"<br>-- concernting RankNTypes and QuantifiedConstraints but nothing I<br>-- tried ended up working.<br><br>-- Thanks in advance for your help.<br>-- Henry Laxen<hr>Haskell-Cafe mailing list<br>To (un)subscribe, modify options or view archives go to:<br><a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe">http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe</a><br>Only members subscribed via the mailman list are allowed to post.</pre></blockquote></div></body></html>