4
\$\begingroup\$

I was recently tasked with creating a function that could generate a "varied" version of some collection of parameters. As in, it should take in a list of parameters, and then vary the value of the first one while leaving the rest fixed -- thus creating some variations. We then move on to the next parameter, and repeat the same process (vary the one we are focusing on, leave other parameters fixed). This continues until we run out of parameters. Parameters are "varied" by looking up an interval of multipliers in a Map, generating num multipliers in that interval, followed by multiplying the parameter by those multipliers to get its varied versions.

I tried solving this problem completely from scratch, rather than using some pre-existing libraries. My approach used the following

  • A zipper so I could have a "cursor" to point to the parameter I was currently focusing on and varying
  • Use the state monad to generate some variations based on the current state of the zipper, then shift the cursor,etc.

I do think my code feels rather overcomplicated and messy though, so I would like some feedback on how I could have done things better.

Further notes:

  • I did use GADTs despite not being very well versed in them. This was because I wanted to impose the Num constraint for my RealInterval datatype.
  • I feel that maybe an Interval typeclass was unnecessary.
{-# LANGUAGE GADTs, MultiParamTypeClasses, FunctionalDependencies, BangPatterns #-}
{-# LANGUAGE DeriveFunctor, DeriveTraversable, DeriveFoldable #-}
import Control.Monad.Trans.State.Lazy
import Data.Function
import Debug.Trace
import qualified Data.Map as M
import Data.Maybe
import Data.List
data Zipper a = Zipper {left :: [a],
 focus :: a,
 right :: [a]}
 deriving (Functor, Traversable, Foldable, Show)
fromList :: [a] -> Maybe (Zipper a)
fromList [] = Nothing
fromList (x:xs) = Just $ Zipper [] x xs
toList :: Zipper a -> [a]
toList (Zipper l f r) = transfer l (f:r)
 where transfer [] l = l
 transfer (x:xs) l = transfer xs (x:l)
 
class Interval i where
 
 -- Generate a bunch of values in the interval, ranging from its start to end, with a step size specified by the 2nd argument.
 range :: (Ord a, Fractional a) => i a -> a -> [a] 
 range i stepSize | stepSize == 0 = []
 | otherwise = go seed []
 where (trueStart, trueEnd) = endpoints i
 (incStart, incEnd) = hasEndpoints i
 next = if trueStart <= trueEnd then subtract stepSize else (+stepSize)
 prev = if trueStart <= trueEnd then subtract stepSize else (+stepSize)
 start = if incStart then trueStart else next trueStart
 end = if incEnd then trueEnd else prev trueEnd
 seed = if start <= end then end else start
 go !curr ls | not $ i `has` curr = ls
 | otherwise = go (prev curr) (curr:ls) -- builds list backwards
 
 -- Generate equally spaced values in the interval (as specified by the integer like number. Returns an empty list if negative, for now.
 linspace :: (Ord b, Fractional b, Integral a) => i b -> a -> [b] 
 linspace i n = range i stepSize
 where (start, end) = endpoints i
 stepSize = (end - start) / fromIntegral (n-1)
 
 endpoints :: Num a => i a -> (a,a) -- Get the endpoints of the interval (start, end)
 
 has :: (Ord a, Num a) => i a -> a -> Bool -- Check for whether a number is within an interval
 
 hasEndpoints :: i a -> (Bool, Bool) -- Tells whether each endpoint of the interval is included
 -- bisect :: Num a => i a -> a -> Maybe (i a, i a) 
-- Attempts to bisect the interval around the provided value, if possible.
data RealInterval a where
 RealInterval :: Num a => (a, Bool) -> (a, Bool) -> RealInterval a
instance Show a => Show (RealInterval a) where
 show (RealInterval s e) = show s ++ " to " ++ show e
-- newtype RealInterval a = RealInterval {getEndpoints :: (Double, Double)}
instance Interval RealInterval where
 
 endpoints (RealInterval s e) = (fst s, fst e)
 
 has i v | prod < 0 = True
 | prod > 0 = False
 | otherwise = l == 0 && hs || r == 0 && he
 where (s, e) = endpoints i
 (hs, he) = hasEndpoints i
 l = v - s
 r = v - e
 prod = l*r
 hasEndpoints (RealInterval s e) = (snd s, snd e)
shift :: Zipper a -> Maybe (Zipper a)
shift (Zipper l f r) = case r of [] -> Nothing
 (x:xs) -> Just $ Zipper (f:l) x xs
varyParams :: (Ord a, Fractional a, Integral b, Interval i) => M.Map a (i a) -> b -> [a] -> [[a]]
varyParams multipliers num params = case fromList params of Nothing -> [[]]
 Just z -> evalState genVar z
 where variations z = do let f = focus z
 m <- maybe [] (flip linspace num) (M.lookup f multipliers)
 pure . toList $ z {focus = m*f}
 genVar = do z <- get
 let v = variations z
 case shift z of Nothing -> pure v
 Just z -> do put z
 rest <- genVar
 pure (v ++ rest)
asked Aug 9, 2022 at 19:45
\$\endgroup\$
0

1 Answer 1

3
\$\begingroup\$

thanks for the question!

This has been an interesting code review for me to do. The author of the code (who I presume is you) seems to clearly possess technical skill in programming, but perhaps is missing knowledge of Haskell idioms.

In no particular order, here are some comments:

  • Some of the language extensions you enable are not actually used, like FunctionalDependencies. They are then just clutter and should be removed. If you run ghc with -Wall -Werror, it will tell you about unused extensions

  • I would advise avoiding unqualified wildcard imports like import Data.Maybe. With more than one such import, it becomes difficult for readers who aren't using IDEs (like me!) to know where imported values are coming from. Prefer either import qualified Data.Maybe as Maybe or import Data.Maybe (maybe, fromMaybe{-, so on -})

  • You note that you've enabled GADTs in order to include the Num constraint in your RealInterval constructor. I would generally advice against doing this. For any constructor with a constraint (such as RealInterval), we can remove the constraint and move it to callsites. This can be annoying, but means that the datatype is more flexible. What if you want a RealInterval of something which is not a Num (for instance, Int)?

    I can't remember where I heard this, but I believe that originally Haskell allowed constraints in types without requiring the GADTs language extension. It was decided that it was better to disallow this, and the feature was removed.

  • Formatting: your formatting has a lot of unnecessary indentation. Perhaps this is intentional? If not, you can indent less as follows:

    Replace do, case, and where clauses that look like

    do a
     b
    case x of y -> ...
     z -> ...
    where x = ...
     y = ...
    

    respectively with

    do
     a
     b
    case x of
     y -> ...
     z -> ...
    where
     x = ...
     y = ...
    
  • Formatting: more generally, your formatting is just very strange for Haskell code. This is not necessarily bad. It's up to you whether or not you want to conform to existing standards. If you do, I would recommend looking up a format guide or using an auto-formatter.

  • Your implementation of has is pretty cool! In particular, I like the prod trick

  • The range function can be implemented more simply as

    range :: (Interval i, Ord a, Fractional a) => i a -> a -> [a]
    range i 0 = []
    range i stepSize =
     reverse $ takeWhile (>= x0') $ iterate (subtract stepSize) xf'
     where
     (x0, xf) = endpoints i
     (h0, hf) = hasEndpoints i
     x0' = if h0 then x0 else x0 + stepSize
     xf' = if hf then xf else xf - stepSize
    

    Generally, your code makes me think you are coming from an imperative language. Idiomatic Haskell usually reads more as a description of what you want from the program rather than a sequence of steps instructing how to get it. For range particularly: "I want the reverse of the prefix greater than x0' of a list constructed by repeated applications of subtract stepSize to xf'

    This can be a strange and difficult transition to make. My only recommendation is to keep writing Haskell, and, in particular, read others' Haskell.

  • You're using where clauses in implementations of function methods. I didn't know you can do that! Neat.

  • You ask if the Interval type class is unnecessary. The answer is... maybe. If the only instance you're using is RealInterval then, yes, the class is unnecessary, because you can replace all uses of types i implementing Interval with uses of RealInterval.

  • On the topic of typeclasses: typically* when writing a typeclass, one defines least number of methods require in order to encapsulate all desired functionality. Other operations, which are defined in terms of these methods, are not included in the typeclass.

    In your case, the interval class only needs endpoints and hasEndpoints: all three of range, has, and linspace can be placed outside the typeclass, because they are implemented in terms of endpoints and hasEndpoints. Note that you'll need to add an Interval i => constraint to each.

    * The only reason I know of to violate this is to allow typeclass instances to provide a more efficient implementation of an operation

Sigh ... I had a lot more to say, but I had to reboot my computer and my work on this question got lost. I hope what I've said so far has been useful, and I'll offer one more thing:

Conceptually, the structure of the varyParams function is this: we have some things (ie, a list of a) and for each thing we have a number of ways we can vary it. A "variation of an a" can be expressed as an a -> a, and "a number of ways to vary an a" is then a [a -> a]. See if you can write a function

vary :: (a -> [a -> a]) -> [a] -> [[a]]

Which accepts a function f :: a -> [a -> a] and list xs :: [a]. The function f gives for each a a number of ways to vary it, and the list xs gives a bunch of as. What is produced are the variations like you have in your original code.

This vary function exposes the structure of varyParams that I was talking about before. This should make the code more readable. Plus, generalizing is fun! (or at least I think so). If you can write vary, you should be able to also use it to re-write varyParams. That is what I had done; sorry that I lost it.

Edit: Oh, yeah! One last thing. Cheers to your use of Zippers! They are so cool.

answered Aug 13, 2022 at 0:50
\$\endgroup\$
1
  • 1
    \$\begingroup\$ Thank you so much for your feedback, it was really helpful! \$\endgroup\$ Commented Aug 13, 2022 at 18:32

Your Answer

Draft saved
Draft discarded

Sign up or log in

Sign up using Google
Sign up using Email and Password

Post as a guest

Required, but never shown

Post as a guest

Required, but never shown

By clicking "Post Your Answer", you agree to our terms of service and acknowledge you have read our privacy policy.

Start asking to get answers

Find the answer to your question by asking.

Ask question

Explore related questions

See similar questions with these tags.