data type familly and makeLenses

Hello, I defined a typeclass like this with a data familly class HasConfig a where data BinocularsConfig a :: * new :: (MonadIO m, MonadLogger m, MonadThrow m) => Maybe FilePath -> m (BinocularsConfig a) getConfig :: Maybe FilePath -> IO (Either String (BinocularsConfig a)) combineWithCmdLineArgs :: BinocularsConfig a -> Maybe ConfigRange -> Maybe (Path Abs Dir) -> BinocularsConfig a update :: (MonadIO m, MonadLogger m, MonadThrow m) => FilePath -> m (BinocularsConfig a) the instance is for now instance HasConfig PreConfig where data BinocularsConfig PreConfig = BinocularsPreConfig { _binocularsPreConfigProjectionType :: ProjectionType } deriving (Eq, Show) [...] Since I use Ini to serialize/un-serialize the configuration, I need lens for this type My question is how can I generate the like easily makeLenses ''(BinocularsConfig PreConfig) does not work thanks for considering Frederic

Could you derive Generic and then use generic lenses?
On Mar 4, 2022, at 06:04, PICCA Frederic-Emmanuel
wrote: Hello, I defined a typeclass like this with a data familly
class HasConfig a where data BinocularsConfig a :: *
new :: (MonadIO m, MonadLogger m, MonadThrow m) => Maybe FilePath -> m (BinocularsConfig a) getConfig :: Maybe FilePath -> IO (Either String (BinocularsConfig a)) combineWithCmdLineArgs :: BinocularsConfig a -> Maybe ConfigRange -> Maybe (Path Abs Dir) -> BinocularsConfig a update :: (MonadIO m, MonadLogger m, MonadThrow m) => FilePath -> m (BinocularsConfig a)
the instance is for now
instance HasConfig PreConfig where data BinocularsConfig PreConfig = BinocularsPreConfig { _binocularsPreConfigProjectionType :: ProjectionType } deriving (Eq, Show)
[...]
Since I use Ini to serialize/un-serialize the configuration, I need lens for this type
My question is how can I generate the like easily
makeLenses ''(BinocularsConfig PreConfig) does not work
thanks for considering
Frederic _______________________________________________ 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.

----- Will Yager
Could you derive Generic and then use generic lenses?
Thanks for the hint, I will install it and I will keep you informed. cheers Fred libghc-generic-lens-dev/stable 2.0.0.0-1 amd64 generically derive traversals, lenses and prisms libghc-generic-lens-doc/stable 2.0.0.0-1 all generically derive traversals, lenses and prisms; documentation libghc-generic-lens-prof/stable 2.0.0.0-1 amd64 generically derive traversals, lenses and prisms; profiling libraries

Use constructor name: makeLenses 'BinocularsPreConfig A minimal example: {-# LANGUAGE TypeFamilies, TemplateHaskell #-} import Control.Lens class HasConfig a where data BinocularsConfig a :: * instance HasConfig () where data BinocularsConfig () = BinocularsPreConfig { _binocularsPreConfigProjectionType :: Int } deriving (Eq, Show) makeLenses 'BinocularsPreConfig works: *Main> :t binocularsPreConfigProjectionType binocularsPreConfigProjectionType :: (Profunctor p, Functor f) => p Int (f Int) -> p (BinocularsConfig ()) (f (BinocularsConfig ())) (In this case it's actually an Iso, as there is just one field). - Oleg On 4.3.2022 12.58, PICCA Frederic-Emmanuel wrote:
Hello, I defined a typeclass like this with a data familly
class HasConfig a where data BinocularsConfig a :: *
new :: (MonadIO m, MonadLogger m, MonadThrow m) => Maybe FilePath -> m (BinocularsConfig a) getConfig :: Maybe FilePath -> IO (Either String (BinocularsConfig a)) combineWithCmdLineArgs :: BinocularsConfig a -> Maybe ConfigRange -> Maybe (Path Abs Dir) -> BinocularsConfig a update :: (MonadIO m, MonadLogger m, MonadThrow m) => FilePath -> m (BinocularsConfig a)
the instance is for now
instance HasConfig PreConfig where data BinocularsConfig PreConfig = BinocularsPreConfig { _binocularsPreConfigProjectionType :: ProjectionType } deriving (Eq, Show)
[...]
Since I use Ini to serialize/un-serialize the configuration, I need lens for this type
My question is how can I generate the like easily
makeLenses ''(BinocularsConfig PreConfig) does not work
thanks for considering
Frederic _______________________________________________ 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.
participants (3)
-
Oleg Grenrus
-
PICCA Frederic-Emmanuel
-
Will Yager