How can I test a smart constructor effectively?

Hello,

Please see the following test (should be self-explaining):

describe "mkPassword" $
    it "ensures the password length is at minimum 10" $ do
        mkPassword "123456789" `shouldBe` Left [PasswordTooShortError]
        mkPassword "123456789a" `shouldBe` Right (Password{passwordRaw = "123456789a"})

        let pass = Password "no!!"
        pass `shouldBe` (Password{passwordRaw = "no!!"})
        show (mkPassword "123456789a") `shouldBe` "Right (Password {passwordRaw = \"123456789a\"})"

I would like to know what possibilities do I have to test the Right branch here.

I saw 2. The first one forces me to exposes the protected Password type itself, with its internals, so itā€™s no good.

Secondly, I thought about matching on the text output with show but this feels pretty fragile, so Iā€™m wondering if I can do better.

Thanks :slight_smile:

Some more context may reveal more what do you want to achieve.

Have you thought of property based approach for example using quickcheck?

If youā€™d have a getRawPassword, then a property could be for all password ā€˜xā€™ that is valid, (getPassword . mkPassword) x == x; and along with a ā€œnegativeā€ property for all invalid password.

Thanks. I suppose I confused you by showing you a passing test, partially with some behavior I didnā€™t want.

I wanted to protect the Password type in my code, by keeping it private to an internal module, and force the callers (from other modules) to initialize it through the mkPassword smart constructor.

That way, only passwords validated according to business rules could flow through the system because thereā€™s no way to initialize them otherwise.

I thought about it more and I got this which Iā€™m happy with (Iā€™m using the hspec testing library btw):

describe "mkPassword" $
    it "ensures the password length is at minimum 10" $ do
        mkPassword "123456789" `shouldBe` Left [PasswordTooShortError]
        case mkPassword "123456789a" of
            Left _ -> expectationFailure "This password should have been rejected!"
            Right _pw -> return ()

If thatā€™s not clear, hereā€™s a bit more context (library code below truncated for brevity):

module Domain.Authentication (mkPassword, PasswordValidationError (..)) where

newtype Password = Password {passwordRaw :: Text} deriving (Show, Eq)

data PasswordValidationError
    = PasswordTooShortError
    | PasswordMustContainUpperCaseError
    | PasswordMustContainLowerCaseError
    | PasswordMustContainNumberError
    deriving (Show, Eq)

mkPassword :: Text -> Either [PasswordValidationError] Password
mkPassword =
    validate
        Password
        [ lengthBetween 10 500 PasswordTooShortError -- this type name is slightly confusing at the moment
        ]
module Domain.Validation where

type Validation error a = a -> Maybe error

validate :: (a -> b) -> [Validation error a] -> a -> Either [error] b
validate constructor validations val =
    case concatMap (\f -> maybeToList $ f val) validations of
        [] -> Right $ constructor val
        errs -> Left errs

This API is a bit confusing, because what can you do with it? You can construct passwords, but there is no way of using them other than Eq and Show.

Why not export the passwordRaw function? Your test assertions can then look like:

(passwordRaw <$> mkPassword "123456789") `shouldBe` Left [PasswordTooShortError]
(passwordRaw <$> mkPassword "123456789a") `shouldBe` Right "123456789a"

This does not in any way compromise the moduleā€™s encapsulation of the constructor.

I should have probably prefaced by saying Iā€™m following along the book called ā€œPractical Web Development with Haskellā€ by Apress, as my intro to Haskell.

I implement tests along the way to make sure I understand things fully and to ensure I can always get back to a know state.

Youā€™re right, rawPassword is meant to be exposed, I hadnā€™t used it yet.

-- module Domain.Authentication
newtype Password = Password {passwordRaw :: Text} deriving (Show, Eq)

rawPassword :: Password -> Text
rawPassword = passwordRaw

Since this is how I intend to access the validated password value:

module MyLib () where

import Data.Text (Text, unpack)
import Domain.Authentication (PasswordValidationError, mkPassword, rawPassword)

saveToDB :: Text -> IO ()
saveToDB pw =
    case mkPassword pw of
        Left errs ->
            putStrLn $ "Validations failed: " ++ show errs
        Right okPw ->
            putStrLn $ "Will hash, then save: " ++ unpack (rawPassword okPw)

{-
*MyLib> saveToDB "123"
Validations failed: [PasswordTooShortError,PasswordMustContainLowerCaseError,PasswordMustContainUpperCaseError]

*MyLib> saveToDB "123456789aB"
Will hash, then save: 123456789aB
-}

Using fmap to test the Either type makes much more sens, thanks @chris-martin!!

Simple; use unsafeCoerce :: a -> b and you can ā€œunpackā€ the smart wrapper in your test project. Be careful though because if you change type into something with different underlying representation you can get silent errors and crashes.

Thanks for the suggestion @bjornkihlberg.

This tool looks quite advanced and probably something I wouldnā€™t use. But could you show me more? Iā€™m not sure I understand what a and b should be in my case.

The doc says:

The highly unsafe primitive unsafeCoerce converts a value from any type to any other type.

To be frank, I donā€™t even understand what converting a value from one type to another type means (without applying a function).

I suppose itā€™s got something to do with the internal memory representation :thinking:

I suppose itā€™s got something to do with the internal memory representation :thinking:

No, it has nothing to do with representation at runtime - itā€™s a compile time cheat. You simply assert to the type system that whatever is returned from unsafeCoerce will always be consistent. Doesnā€™t mean that itā€™s true. I think the C++ equivalent would be type casting.

So for example you could do this:

let x :: Int
    x = 5
    y :: Bool
    y = unsafeCoerce x

y isnā€™t actually a boolean now. The type system think it is but itā€™s actually an integer. This is very dangerous. It sounds like you should stay away from this alternative. I of course leave that up to you. I would personally say itā€™s a case of ā€œlearn the rules before breaking themā€ but thatā€™s just my opinion.

A safe approach is to create an unwrapping procedure and/or wrapping procedure in the module where you keep your protected data types:

module MyModule
  ( Positive
  , positive
  , unsafeWrapPositive
  , unsafeUnwrapPositive
  ) where

newtype Positive = Positive Int

tryPositive :: Int -> Maybe Positive
tryPositive x = if x > 0 then Just (Positive  x) else Nothing

unsafeWrapPositive :: Int -> Positive
unsafeWrapPositive = Positive

unsafeUnwrapPositive :: Positive -> Int
unsafeUnwrapPositive (Positive x) = x

Notice how the constructor of Positive isnā€™t directly exposed

Mmm, I was a little confused at first, because it looks like something got messed up with your copy/paste and you probably meant something like this?

module MyModule (
    Positive,
    tryPositive,
    safeWrapPositive,
    safeUnwrapPositive,
    unsafeWrapPositive,
    unsafeUnwrapPositive,
) where

import Unsafe.Coerce (unsafeCoerce)

newtype Positive = Positive Int deriving (Show)

tryPositive :: Int -> Maybe Positive
tryPositive x = if x > 0 then Just (Positive x) else Nothing

safeWrapPositive :: Int -> Positive
safeWrapPositive = Positive

safeUnwrapPositive :: Positive -> Int
safeUnwrapPositive (Positive x) = x

unsafeWrapPositive :: Int -> Positive
unsafeWrapPositive = unsafeCoerce

unsafeUnwrapPositive :: Positive -> Int
unsafeUnwrapPositive = unsafeCoerce

I can then see the unsafe versions are equivalent to the safe versions:

ghci> unsafeUnwrapPositive . safeWrapPositive $ 3
3
                
ghci> safeUnwrapPositive . unsafeWrapPositive $ 3
3

ghci> Just n = tryPositive 3
ghci> n
Positive 3

ghci> unsafeUnwrapPositive n
3

ghci> safeUnwrapPositive n
3

Thanks for teaching me this technique. Iā€™d have to understand Haskell fundamentals better to feel good using it but itā€™s interesting nonetheless :slight_smile:

unsafeCoerce is an extraordinary topic to bring up in response to this quite ordinary situation!

Maybe not an answer to your question, but the password library also does this.
Thereā€™s an unsafeShowPassword for exactly this reason. Sometimes you just need to get to the password; itā€™s prefaced with unsafe to show that youā€™d better have a good reason to use it.
(testing for correctness definitely is one of those reasons)

On stackoverflow, shang answers a similar question like this:

The usual convention is to split your module into public and private parts, i.e.

module SomeModule.Internal where

-- ... exports all private methods

and then the public API

module SomeModule where (export1, export2)

import SomeModule.Internal

Then you can import SomeModule.Internal in tests and other places where its crucial to get access to the internal implementation.

The idea is that the users of your library never accidentally call the private API, but they can use it if the know what they are doing (debugging etc.). This greatly increases the usability of you library compared to forcibly hiding the private API.

1 Like

Thanks @jaror it looks like a great tip :slight_smile:

Although I suppose the argument could be made that testing private APIs could be counter productive (being an implementation detail). Nice to know though. Iā€™ve also been thinking that doctests may help testing private functions but I have yet to try it.

Here, I wanted to test the API the same way the library consumer would interact with. @chris-martin put me on the right track since all I needed was mapping to a function I already had in the end.

Thanks @Vlix, it looks like a cool library :slight_smile:

The world ā€œunsafeā€ here seems to be only a hint about the fact that this is data you donā€™t want to leak into your logs, etc. The unsafeShowPassword function in this lib looks equivalent to my function rawPassword: