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.
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
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.
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.
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
I suppose itās got something to do with the internal memory representation
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
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)
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.
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.
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: