I need your help/adviсe/suggestion

After 1 year of studying haskell, I decided to write small library which parses command line args.

And since I haven’t had much experience in haskell, I would ask your help.

I would ask you all to see the code and mention what I can improve, maybe there is somewhere memory leaks or performance issues, or maybe you have some your own best practices of how to orgranise the code and so on and so forth.

I haven’t made tests and benchmarks, yet.

I haven’t move String to Text yet.

Also, I left the example in the example folder and also I left comments in the code so you might understand what is going on there

So, I please you very hard, look on the code and make your suggestions/advices. And, please, look on example folder, I made question there about existential type

And sorry for english here and in the comments in the repo, English is not my native

thank you

https://github.com/max-grek/flags

Some things that I noticed with a cursory inspection:

  1. A helper function like the following would be nice
    (not just to reuse, but also because it’s not stringly typed, i.e. if you mistype Bool it’ll tell you, it won’t if you mistype "Bool")
{-# LANGUAGE TypeApplications #-}
import Data.Proxy (Proxy (..))
import Data.Typeable (typeOf, typeRep)

valueIsBool :: Value -> Bool
valueIsBool (Value v) = typeOf v == typeRep (Proxy @Bool)
  1. You seem to use the go helper in where pattern in places where a case would suffice. AND you don’t have to keep giving arguments to helper functions if they are already top level (i.e. the pair here for check_for_arg, since it’s not recursive.
test :: (String,String) -> HashMap String Value -> Either Error ()
test pair@(k1, k2) m =
    case Map.lookup k1 m of
        Nothing -> Left $ UnknownFlag k1
        Just v -> check_for_arg v >> checkForCompatibility pair v
  where
    check_for_arg :: Value -> Either Error ()
    check_for_arg (Value v)
      | valueIsBool v && (not $ null k2) =
        Left . FlagSyntax $ k1 <> " must not have arg"
      | not (valueIsBool v) && null k2 =
        Left . FlagSyntax $ k1 <> " must have arg"
      | otherwise = Right ()
  1. ALSO, most prefer checkForArg, because snake case is used for C FFI functions, but most importantly because of Haskell’s use of space as semantically significant, the underscores sometimes seem like spaces, so it makes you do a double take that it isn’t check for arg which is a function with two arguments, instead of check_for_arg which is just a function.
myFunc = map (some_underscores_func 5) someList -- compare the following
myFunc = map (some underscores func 5) someList -- similar but very different
myFunc = map (someUnderscoresFunc 5) someList   -- very distinct and immediately obvious
  1. Why splitOn and then intercalate? If you just want the first one “popped off” do the following:
-- where `delim :: Char`
case break (== delim) xs of
    (_, []) -> Nothing
    (x, rest) -> Just (x, drop 1 rest)
  1. Prefixing underscores to top-level functions is not great, since you won’t get warnings if you never use them (this can lead to dead code accumulating). If you’re using the functions, don’t prefix underscores.

  2. I see a lot of fst pair and snd pair when you could just pattern match on the pair and name the first and second part of the pair. Then again, you could have also given two arguments instead of a pair, also avoids unpacking and repacking.

There’s also some higher level decisions about the package that I would have done differently, like why add in the dash to then later remove it again. Just add it in the error messages if it’s for pretty printing. And the result type of checkAndBuild I would make Either Error [(String, Maybe Value)], so you don’t use empty string as a Nothing and combine deduceStrategy and applyChecks so you can immediately return the Value after you do a readMaybe.

A lot of this feels like you could learn from this great article by Alexis King: Parse, don’t validate, because you’re validating a lot (hence the boolean checks and all the Right (), which are a dead giveaway) and parsing would make it more robust and also simpler in the end.

First of all, thank you a lot. From your suggestions I learned a lot, thank you one more time

While I’m still rewriting the code based on your ideas, I have one question that I’m interested in.

let’s suppose I have the following code

data Config = Config Http deriving stock Show

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

flags :: NonEmpty (Flag Short)
flags =
    -- http flags
    define "http-host" "0.0.0.0" "http host"  <>
    define "http-port" (9000 :: Int) "http port" <>
    define "http-bool" Flase "http bool exampl2" <>
    define "http-bool2" False "http bool2 example"

setHttp :: Http -> (String,Value) -> Http
setHttp x ("http-host", Value v)  = x {getHttpHost = show v}
setHttp x ("http-port", Value v)  = x {getHttpPort = read @Word16 $ show v}
setHttp x ("http-bool1", Value v) = x {getHttpBool1 = read @Bool $ show v}
setHttp x ("http-bool2", Value v) = x {getHttpBool2 = read @Bool $ show v}
setHttp x _                       = x

main :: IO ()
main = do
  args <- getArgs
  case parseArgs flags args of
    Left e -> do
      print e
      exitFailure
    Right v -> do
      let kv = Map.toList v
          result = foldl setHttp mkHttp kv
          cfg = Config result
      print cfg

and I want to get the data from existential type. I noticed, that I need to run “show” and then “read” but it’s very tedious and I don’t think that this good approach.
Do you know how to improve that code? I’ll appreciate very hard if you give me an answer

Well, since it might fail, you’re going to get either a Maybe, Either, etc. or you error out.

But since you’ve got a Typeable a on Values, you can make a function like this:

{-# LANGUAGE ScopedTypeVariables #-}
fromValue :: forall a. Typeable a => Value -> Maybe a
fromValue (Value v) =
    v <$ guard (typeOf v == typeRep (Proxy @a))

or

{-# LANGUAGE ScopedTypeVariables #-}
fromValue :: forall a. Typeable a => String -> Value -> a
fromValue name (Value v) =
    | vType == typeRep (Proxy @a) = v
    | otherwise = error $ "Wrong type for " <> name <> ": " <> show vType
  where
    vType = typeOf v