(I'm totally rewriting this question to give it a better focus; you can see the history of changes if you want to see the original.)
Let's say I have two modules:
inverseAndSqrt
. What this function actually does is not important; what is important is that it returns none, one, or both of two things in a way that the client can distinguish which one is which;module Module1 (inverseAndSqrt) where
type TwoOpts a = (Maybe a, Maybe a)
inverseAndSqrt :: Int -> TwoOpts Float
inverseAndSqrt x = (if x /= 0 then Just (1.0/(fromIntegral x)) else Nothing,
if x >= 0 then Just (sqrt $ fromIntegral x) else Nothing)
inverseAndSqrt
and on its typemodule Module2 where
import Module1
fun :: (Maybe Float, Maybe Float) -> Float
fun (Just x, Just y) = x + y
fun (Just x, Nothing) = x
fun (Nothing, Just y) = y
exportedFun :: Int -> Float
exportedFun = fun . inverseAndSqrt
What I want to understand from the perspective of design principle is: how should I interface Module1
with other modules (e.g. Module2
) in a way that makes it well encapsulated, reusable, etc?
The problems I see are
TwoOpts
type synonym doesn't solve anything, as Module1
could still change its implementation thus breaking client code.Module1
is also forcing the type of the two optionals to be the same, but I'm not sure this is really relevant to this question...How should I design Module1
(and thus edit Module2
as well) such that the two are not tightly coupled?
One thing I can think of is that maybe I should define a typeclass
expressing what "a box with two optional things in it" is, and then Module1
and Module2
would use that as a common interface. But should that be in both module? In either of them? Or in none of them, in a third module? Or maybe such a class
/concept is not needed?
I'm not a computer scientist so I'm sure that this question highlights some misunderstanding of mine due to lack of experience and theoretical background. Any help filling the gaps is welcome.
get1of2
/get2of2
(let's say these are the name we use when we first design Module1
) vs get1of3
/get2of3
/get3of3
.Just
the sum¹ of the two main contents only if they are both Just
s, or a Nothing
if at least one of the two main contents is a Nothing
. I guess in this case the internal representation of this class would be something like ((Maybe a, Maybe a), Maybe b)
(¹ The sum is really a stupid example, so I've used b
here instead of a
to be more general than the sum would require).Don't define a simple type alias; this exposes the details of how you implement TwoOpts
.
Instead, define a new type, but don't export the data constructor, but rather functions for accessing the two components. Then you are free to change the implementation of the type all you like without changing the interface, because the user can't pattern-match on a value of type TwoOpts a
.
module Module1 (TwoOpts, inverseAndSqrt, getFirstOpt, getSecondOpt) where
data TwoOpts a = TwoOpts (Maybe a) (Maybe a)
getFirstOpt, getSecondOpt :: TwoOpts a -> Maybe a
getFirstOpt (TwoOpts a _) = a
getSecondOpt (TwoOpts _ b) = b
inverseAndSqrt :: Int -> TwoOpts Float
inverseAndSqrt x = TwoOpts (safeInverse x) (safeSqrt x)
where safeInverse 0 = Nothing
safeInverse x = Just (1.0 / fromIntegral x)
safeSqrt x | x >= 0 = Just $ sqrt $ fromIntegral x
| otherwise = Nothing
and
module Module2 where
import Module1
fun :: TwoOpts Float -> Float
fun a = case (getFirstOpts a, getSecondOpt a) of
(Just x, Just y) -> x + y
(Just x, Nothing) -> x
(Nothing, Just y) -> y
exportedFun :: Int -> Float
exportedFun = fun . inverseAndSqrt
Later, when you realize that you've reimplemented the type product, you can change your definitions without affecting any user code.
newtype TwoOpts a = TwoOpts { getOpts :: (Maybe a, Maybe a) }
getFirstOpt, getSecondOpt :: TwoOpts a -> Maybe a
getFirstOpt = fst . getOpts
getSecondOpt = snd . getOpts