Hi Josh,
I just tried a quick experiment with stack resolver lts-11.2 and I'd like to share the results as there are interesting:
1. Consider the following module setup that's a simplified version of your situation
Dependencies:
- Main depends on Hi
- Hi depends on Hum
- Hee depends on Hum
Main.hs:
```
module Main where
import Hi
import Hee
main :: IO ()
main = print $ hi ++ hee ++ "!"
```
Hee.hs:
```
module Hee (hee) where
import Hum (hum)
hee :: String
hee = "hee1" ++ hum
```
Hi.hs
```
module Hi (hi) where
import Hum (hum)
hi :: String
hi = "hi1" ++ hum
```
Hum.hs
```
module Hum (hum) where
hum :: String
hum = "hum"
```
2. Now build it once with `stack build`.
3. Now change "hum" to "hum1" and run `stack build` notice that all 4 modules will recompile.
4. Now add {-# NOINLINE hum #-} just above hum :: String and run `stack build`
5. Change hum again and run `stack build`.
6. Only Hum will recompile!
Lesson:
Add NOINLINE to any function/value that you change frequently and don't
want to trigger massive recompilations. This does come at a performace
tradeoff since GHC will not be able to inline whatever you added that
pragma to, but your compile-time will be saved. In your case of
hard-coded data, I think you won't be able to measure any performance
penalty.
Hope that helps,