Make function that produces default value with monoid

Hi, all.

Let’s suppose I have existential type and function that unwrap the data:

data Value = forall a . (Typeable a, Read a) => Value a deriving stock Show

fromValue :: forall a . Typeable a => Value -> Maybe a
fromValue (Value v)
  | typeOf v == typeRep (Proxy @a) = cast v
  | otherwise = Nothing

and I have the following code:

data Http
  = Http
  { getHttpHost  :: !String
  , getHttpPort  :: !Word16
  , getHttpBool1 :: !Bool
  , getHttpBool2 :: !Bool
  }
  deriving stock (Show)

setHttp :: Http -> (String,Value) -> Http
setHttp x ("http-host", v)  = x {getHttpHost = fromMaybe "" fromValue @String v}
setHttp x ("http-port", v)  = x {getHttpPort = fromMaybe 0 fromMaybe @Int v}

I don’t like that boilerplate with fromMaybe

I’m trying to write the code that create default value automatically with help of Monoid, like this one, and the following example works for any Num type:

numDefault :: forall a . (Monoid a, Typeable a, Num a) => Value -> a
numDefault (Value v) = fromMaybe (getSum . mempty $ Sum @a) $ cast @_ @a v

But I can’t compose that function with another one, like in the next example, since ghc complains that I need to add Num type class here, however if I add it, it won’t work with Strings and Bool:

fromValue :: forall a . (Monoid a, Typeable a) => Value -> a
fromValue val@(Value v)
  | typeOf v = typeRep (Proxy @Integer) = numDefault @a val
  | otherwise = mempty @a

Does anyone know, how to implement that behaviour? I don’t any ideas since I don’t have enough knowledge.

I will appreciate for any hints

First of all, I think you should try to avoid using Typeable as much as possible. Have you tried a simple ADT:

data Value = IntVal Int | StringVal String

You can add more cases as needed.


With that disclaimer out of the way, let me try to respond to your main question. If Int had a Monoid instance with mempty = 0, then you could just define your alternative fromValue function like so:

fromValue' :: (Typeable a, Monoid a) => Value -> a
fromValue' x = fromMaybe mempty (fromValue x)

But alas, Int does not have a canonical Monoid structure (you could also take multiplication and 1).

The question you have to ask yourself is what 0 and "" mean in the context of HTTP. Why would you default to those values? Perhaps you should introduce a newtype Port like so:

newtype Port = Port Word16
instance Semigroup Port where
  Port x <> Port y = Port (x + y)
instance Monoid Port where
  mempty = Port 0

But honestly, it doesn’t make much sense to me to add up port numbers. And the 0 port is also not something you usually use as far as I know.

If you’re just using those default values to signal the absence of a value, then you should instead modify your Http type to reflect that those parts could be absent:

data Http
  = Http
  { getHttpHost  :: !(Maybe String)
  , getHttpPort  :: !(Maybe Word16)
  , getHttpBool1 :: !Bool
  , getHttpBool2 :: !Bool
  }

Then you don’t need fromMaybe.

Of course this can have an impact on performance (and you might want to use a strict Maybe type), but I think you should first have a clear idea of what a correct solution to your problem looks like.

Perhaps a more performant solution would to introduce your own class:

class Absent a where
  absent :: a
instance Absent Port where
  absent = Port 0
instance Absent Hostname where
  absent = Hostname ""

fromValue' :: (Absent a, Typeable a) => Value -> a
fromValue' x = fromMaybe absent (fromValue x)

that’s a problem, I can’t add ADT, since I want that user might use any type he/she wants
(for studying purposes, I’m developing this tiny library, to parse command-line arguments
GitHub - max-grek/flags)

I’ll take a look on your suggestion

BTW, why I should avoid Typeable?

Because it is often complicated, restrictive, and slow. In your case you’re using it to do dynamic typing, which means the compiler cannot help you or your users with type errors. For example, I think in your implementation if you make a typo in a flag name, then you’ll only get an error at run time.

(By the way, your Value already exists in base and is called Dynamic)

If you want to see an idiomatic statically typed command-line argument parsing library, I’d recommend optparse-applicative. Apparently there is also a blog post presenting the main implementation technique: Applicative option parser.

1 Like

thanks for the hint, and thanks for the answer, I’ll take a look