About your example:
module Some.Namespace.VeryLongModuleName where
import Some.Namespace.VeryLongModuleName as SomeSemanticallyFittingName (A(..))
import Some.Namespace.VeryLongModuleName as SomeOtherSemanticallyFittingName (B(..))
data A = MkA {a :: Int}
data B = MkB {a :: Int}
x :: B -> B
x y = y {SomeOtherSemanticallyFittingName.a = 3}
You can mix and match imports:
import Some.Namespace.VeryLongModuleName (A, B)
import qualified Some.Namespace.VeryLongModuleName as SomeSemanticallyFittingName hiding (A(..), B(..))
import qualified Some.Namespace.VeryLongModuleName as A (A(..))
import qualified Some.Namespace.VeryLongModuleName as B (B(..))
x :: B -> B
x y = y {B.a = 3}
and leave SomeSemanticallyFittingName for other functions you see fit. It doesn’t make sense to name the qualified B import as SomeSemanticallyFittingName if you’re importing B to use as B anyways.
-- if you had this
import qualified Some.Namespace.VeryLongModuleName.VeryLongAbstractFactoryPatternName as VeryLongAbstractFactoryPatternName (VeryLongAbstractFactoryPatternName(..))
-- you could get away with
import qualified Some.Namespace.VeryLongModuleName.VeryLongAbstractFactoryPatternName as FactoryB (FactoryB(..))
-- with proper namespacing and isolating crucial records on one record per file basis (like public classes in Java)
Another alternative:
{-# LANGUAGE RecordWildCards #-}
x :: B -> B
x (MkB {..}) = MkB {a = 3, ..}
For short types, prefixing fields saves you the imports, but for long types, smart module imports win:
data VeryLongThing = MkT {veryLongThingName :: String}
...
-- redundant synonym made later by user
vltName = veryLongThingName
-- vs
data VeryLongThing = MkT {name :: String}
import Module.Thing (VeryLongThing)
import qualified Module.Thing as VLT (VeryLongThing(..))
...
VLT.name
-- still have the possibility of synonym
vltName = VLT.name
There might be an opportunity to do some bikeshedding to make imports more palatable like allowing something like:
import Some.Namespace.VeryLongModuleName (A, B)
qualified as SomeSemanticallyFittingName hiding (A(..), B(..))
A (A(..))
B (B(..))
Everything
C hiding (C(..))
I think making naming more convenient is a good way to go because implementing SetField is HELL, not even optics can save it, you need to remake the system from the ground up with optics (I wouldn’t mind).