[Haskell-cafe] Unused type-classes triggering a recompilation?

Saurabh Nanda saurabhnanda at gmail.com
Wed Oct 18 17:23:20 UTC 2017


Hi,

We're trying to optimise the way lenses are built and imported in our
project (there are 500+ of them!) . In the simplified version that I have
presented below, whenever a new HasX class is added to the LensClasses
module, both User & Main end up getting recompiled even though they have
nothing to do with the newly added type-class. I've read and re-read
"Recompilation Avoidance" [1], but haven't been able to figure out why this
would be happening.

PS: To work-around this issue we've had to give each HasX class an
independent module of its own. We specifically import only those which are
required (all of this is done via a code-gen tool). This has resulted in an
explosion of modules and is probably causing slow-down of our build process
[2]

*LensClasses.hs:*

    {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
FlexibleInstances #-}
    module LensClasses where
    import Control.Lens
    class HasName s a | s -> a where name :: Lens' s a
    class HasEmail s a | s -> a where email :: Lens' s a
    class HasAge s a | s -> a where age :: Lens' s a

*User.hs (which defines a few lenses for the User record):*

    {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
TypeSynonymInstances, FlexibleInstances #-}
    module User
      ( module User
      , HasName(..)
      , HasEmail(..)) where
    import LensClasses(HasName(..), HasEmail(..), HasVariantName(..))
    data User = User  { _userName :: String  , _userEmail :: String  }
deriving (Eq, Show)
    instance HasName User String where
      {-# INLINE name #-}
      name fctor (User name_ email_) = fmap (\dragon -> User dragon email_)
(fctor name_)
    instance HasEmail User String where
      {-# INLINE email #-}
      email fctor (User name_ email_) = fmap (\dragon -> User name_ dragon)
(fctor email_)

*Main.hs (the final call site/s):*

    module Main where
    import Control.Lens
    import User
    main :: IO ()
    main = do
      let u = User "saurabh" "saurabhnanda at gmail.com"
      putStrLn $ u ^. name

[1]
https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/RecompilationAvoidance

[2]
https://www.reddit.com/r/haskell/comments/76zljl/hotswapping_haskell_at_facebook_jon_coens/doi0s4q/
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20171018/7252f775/attachment.html>


More information about the Haskell-Cafe mailing list