Is overtype safety good or not?

Hi everyone. I need your advices in the next question:

when you write the code, are you using over type safety or not? let me explain, what I mean:

For example:
I want that when I parse data from stdin, I get the the valid data, non empty strings in that case and nonEmpty numeric values

data Http'
  = Http'
  { getHttpHost    :: Maybe Text
  , getHttpPort    :: Maybe Word16
  , getHttpTimeout :: Maybe Text
  } deriving stock Show

Then I want to see error message of validation like this

-- ("Http", "http host must not be empty" :| [])
type Error = (String, NonEmpty String)

also I want that validated data type will be signed as validated in type level

data Http'
  = Http'
  { getHttpHost    :: Maybe Text
  , getHttpPort    :: Maybe Word16
  , getHttpTimeout :: Maybe Text
  } deriving stock Show

newtype Http = Http Http' deriving stock Show
-- or
newtype ValidatedHttp = ValidatedHttp Http' deriving stock Show

validate :: Http' -> Either (NonEmpty Error) Http
-- or
validate :: Http' -> Either (NonEmpty Error) ValidatedHttp

and in the end it looks like this

-- if Http is Valid
Right (Http (Http' {getHttpHost = Just "fdsfs", getHttpPort = Just 0, getHttpTimeout = Just "fdsfsd"}))
-- if Http is not Valid
Left (("Http","host must not be empty" :| ["port must not be empty","timeout must not be empty"]) :| [])

Is it okay that I do so many type safety things

If we use Either we assume that Left has some kind of an error, right? and we don’t need to emphasize that Left might be empty or not?

What about ValidatedHttp? Is it okay to return validated structure or not?

What about getHttpHost :: Maybe Text? Is it okay to move Maybe Text to NonEmpty Text

I’ve read many times these articles, but I’m not sure that what I’m doing is a right way
https://www.parsonsmatt.org/2017/10/11/type_safety_back_and_forth.html
https://lexi-lambda.github.io/blog/2019/11/05/parse-don-t-validate/

Thanks in advance

Sorry for English, it’s not my native

3 Likes

I would not bother using NonEmpty. A minor annoyance for in my opinion close to zero additional safety.

If your constructors are smart, I don’t think you need an Http'/ValidateHttp dichotomy.

Just have a

type Port = Word16
type Host = Text
    -- And so on

mkHttp :: Port -> Text -> Either [Error] Http
mkHttp = undefined

and it should be enough.

3 Likes

The idea is to represent valid states only. Rather than validating data over and over to ensure a function returns correctly (and maybe forgetting to validate and needing a future debug session to figure out what is failing to validate and triggering errors), you represent valid data.

Validation:

data Http = Http
  { getHttpHost    :: String
  , getHttpPort    :: Integer
  , getHttpTimeout :: String
  } deriving Show

validate :: Http -> Bool
validate h
  | getHttpHost h == ""    = False
  | getHttpPort h <= 0     = False
  | getHttpTimeout h == "" = False
  | otherwise              = True

connect :: Http -> IO ()
connect = undefined

get :: Http -> Either String (IO ())
get req = if validate req then Right (connect req) else Left "Some error"

post :: Http -> Either String (IO ())
post req = if validate req then Right (connect req) else Left "Some error"

put :: Http -> Either String (IO ())
put req = if validate req then Right (connect req) else Left "Some error"

delete :: Http -> Either String (IO ())
delete req = if validate req then Right (connect req) else Left "Some error"

Parsing:

parse :: String -> Integer -> String -> Either String Http
parse host port timeout
  | host == ""    = Left "No host"
  | port <= 0     = Left "Invalid port"
  | timeout == "" = Left "No timeout"
  | otherwise     = Right $ Http { getHttpHost = host
                                 , getHttpPort = port
                                 , getHttpTimeout = timeout
                                 }

get' :: Http -> IO ()
get' = connect

post' :: Http -> IO ()
post' = connect

put' :: Http -> IO ()
put' = connect

delete' :: Http -> IO ()
delete' = connect

Another thing you might ask about:

data Http'
  = Http'
  { getHttpHost    :: Maybe Text
  , getHttpPort    :: Maybe Word16
  , getHttpTimeout :: Maybe Text
  } deriving stock Show

Should I put Maybe everywhere? The answer is: IF the Maybe represents a valid state.
You might say “yes, when I use Maybe, I use a default port 8080 when I try to do a GET on it”.
In this case, no, the maybe doesn’t need to exist inside Http, you can do:

parse :: String -> Maybe Integer -> String -> Either String Http

and set the port accordingly.
If the port can mean Nothing, and you will work with that Nothing, then it shall be Nothing, and handled accordingly. I don’t know what can you do with a Nothing port though.

And finally, errors. How do you represent them?
Matt has a blog post talking about errors: The Trouble with Typed Errors
You can do them stringly typed:

f :: Http -> Either String (IO ())

Typed errors:

data MyError
  = NoHost
  | InvalidPort
  | InvalidTimeout
  | CantConnect

f :: Http -> Either MyError (IO ())

And exceptions:

data HttpException = ConnectionException
  deriving Show

instance Exception HttpException

f :: Http -> IO ()
f h = throwIO ConnectionException

Or perhaps something more modern, like effect systems, so you know which exception goes where rather than bundling everything in IO and who knows who throws what.

Honestly: this problem is not 100% comfortably solved, in any language. Rust spent years debating this and settled on using anyhow or thiserror depending on if you’re doing a library or an executable, as the less painful way. Opinions all around.
So as a rule of thumb (maybe):

  1. If you can’t recover (no, 20 nested pattern matches on Result with no cleanups and just logging is not recovery), exceptions.
  2. If you are willing to deal with the propagation of typed errors sooner rather than later, or you’re building an API, then typed errors.
  3. If you are going to pop a message to somebody somewhere, just string it. Let us be honest, you’re not even going to pattern match on the string, you’re going to log it and move on. Somebody keeps fat fingering the keyboard and inputting “banana” as a port, no default will save you or give the user a sensible response.
10 Likes

that’s almost exactly what I was looking for, thanks a lot

several questions:

  1. so, if I get the data from stdin and there might be an empty string, I have to reject that and I don’t need to propagate an empty string as Maybe String - I need to propagate String, right? Because, as you said - the idea is to represent valid states only
  2. if I have field like getHttpHost :: Maybe String, somewhere, it means that my logic works with Nothing and Just somehow, right? The valid state passed to function a is Maybe String. Am I right?

If the empty string is useless then yes. If you are going through a Maybe chain of 10 functions only to match on Nothing at the end and return a “Something happened” string, why not deal with it at the source?

Sometimes you do need the Maybe. For example, when the Nothing represents information to be determined by an automated service that is going to be running 1 hour from now.

As you start thinking about the domain, you will notice this:

data Maybe a = Just a
  | Nothing

morphs into this:

data Port a = SomePort a
  | ToBeDeterminedLater

Something more meaningful.

Yes.

There are valid cases when you can use Maybe. For example, database nulls. If your database has nulls you can’t just default into a value, you can represent them if you want a faithful representation of your data.

Giving meaning to the Maybe, same as above:

data DBValue a = DBValue a
  | DBNull
2 Likes