Enlico
Enlico

Reputation: 28450

Writing modules in Haskell the right way

(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:

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)
module 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

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.

Possible modifications I'd like to support

Upvotes: 1

Views: 431

Answers (2)

luqui
luqui

Reputation: 60503

To me, Haskell design is all type-centric. The design rule for functions is just "use the most general and accurate types that do the job", and the whole problem of design in Haskell is about coming up with the best types for the job.

We would like there to be no "junk" in the types, so that they have exactly one representation for each value you want to denote. E.g. String is a bad representation for numbers, because "0", "0.0", "-0" all mean the same thing, and also because "The Prisoner" is not a number -- it is a valid representation that does not have a valid denotation. If, say for performance reasons, the same denotation can be represented multiple ways, the type's API should make that difference invisible to the user.

So in your case, (Maybe a, Maybe a) is perfect -- it means exactly what you need it to mean. Using something more complicated is unnecessary, and will just complicate matters for the user. At some point whatever you expose will have to be convertible to a Maybe a for the first thing and a Maybe a for the second thing, and there is no extra information than that, so the tuple is perfect. Whether you use a type synonym or not is a matter of style -- I prefer not use synonyms at all and only give types names when I have a more formal abstraction in mind.

Connotation is important. For example, if I had a function for finding the roots of a quadratic polynomial, I probably wouldn't use TwoOpts, even though there are at most two of them. The fact that my return values are all "the same kind of thing" in an intuitive sense makes me prefer a list (or if I'm feeling particularly picky, a Set or Bag), even if the list has at most two elements. I just have it match my best understanding of the domain at the time, so I won't change it unless my understanding of the domain has changed in a significant way, in which case the opportunity to review all its uses is exactly what I want. If you are writing your functions to be as polymorphic as possible, then often you won't need to change anything but the specific moments the meaning is used, the exact moment domain knowledge is required (such as understanding the relationship between TwoOpts and Set). You don't need to "redo the plumbing" if it's made of a sufficiently flexible, polymorphic material.

Supposing you didn't have a clean isomorphism to a standard type like (Maybe a, Maybe a), and you wanted to formalize TwoOpts. The way here is to build an API out of its constructors, combinators, and eliminators. For example:

data TwoOpts a    -- abstract, not exposed

-- constructors 
none :: TwoOpts a
justLeft :: a -> TwoOpts a
justRight :: a -> TwoOpts a
both :: a -> a -> TwoOpts a

-- combinators
-- Semigroup and Monoid at least
swap :: TwoOpts a -> TwoOpts a

-- eliminators
getLeft :: TwoOpts a -> Maybe a
getRight :: TwoOpts a -> Maybe a

In this case the eliminators give exactly your representation (Maybe a, Maybe a) as their final coalgebra.

-- same as the tuple in a newtype, just more conventional
data TwoOpts a = TwoOpts (Maybe a) (Maybe a)

Or if you wanted to focus on the constructors side you could use an initial algebra

data TwoOpts a
    = None
    | JustLeft a
    | JustRight a
    | Both a a

You are at liberty to change this representation as long as it still implements the combinatory API above. If you have reason to use different representations of the same API, make the API into a typeclass (typeclass design is a whole other story).

In Einstein's famous words, "make it as simple as possible, but no simpler".

Upvotes: 3

chepner
chepner

Reputation: 531718

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

Upvotes: 1

Related Questions