How to implement C# out parameters in C++?

C++ lacks the syntactic sugar of C# and leaves the developer with several options to implement out parameters. Either declare the function parameter as a double pointer (which passes the pointer by value) or as a reference to a pointer (which passes the pointer by reference). The former case looks as follows:

void createRect(Rect **r)
{
    *r = new Rect(1, 2);
}

int main(int argc, char **argv)
{
    Rect *p;
    createRect(&p);
    return 0;
}

In this case we pass the Rect pointer by value and this is why we need to have a double pointer in the function declaration. Note that if there is a single pointer in the function declaration, the changes of r will remain only in the scope of the createRect function.

The second option looks as follows:

void createRect(Rect *&r)
{
    r = new Rect(1, 2);
}

int main(int argc, char **argv)
{
    Rect *r;
    createRect(r);
    return 0;
}

Note that in this case the pointer is passed by reference and the function works directly with the pointer instead with its copy. Also, the changes made in the createRect function are visible to the caller.

Using QuickCheck with Custom Data Types

QuickCheck is awesome! But trying to figure out how to use it with custom data types could be hard for newbies like me. The documentation assumes that you are already fluent in Haskell and hardly provides explanations or code snippets. Hopefully, the following two examples will give you a glimpse of the syntax and help you make your way out of the numerous compiler errors.

Let’s start with defining a simple data type Point that holds two Int values:

module QCSamples where
import Test.QuickCheck

data Point = Pt Int Int

instance Show (Point) where 
  show (Pt x y) = "{" ++ show x ++ "," ++ show y ++ "}"

To use the Point data type in QuickCheck, we need to provide an implementation of Arbitrary:

instance Arbitrary Point where
   arbitrary = do
     x <- arbitrary
     y <- arbitrary
     return $ Pt x y

Note that in the above example we only need to say x<-arbitrary and y<-arbitrary to get the random Ints. Haskell will infer their type from the specification of Point and will provide the appropriate arbitrary implementation, i.e. Int. So, now we can let QuickCheck produce random Points.

*QCSamples> sample $ (arbitrary :: Gen Point)
{-1,1}
{0,-2}
{-1,1}
{8,-4}
{-19,8}
{-60,4}
{-126,-71}
{-87,156}
{307,-248}
{1977,322}
{1593,3628}
*QCSamples>

Now, let's have a look at a slightly harder example:

data Set a = Set [a]

instance (Show a) => Show (Set a) where
     show s = showSet s where
          showSet (Set []) = "{}"
          showSet (Set (x:xs)) = "{" ++ show x ++ showSubSet xs ++ "}" where
               showSubSet [] = ""
               showSubSet (x:xs) = "," ++ show x ++ showSubSet xs

Here is the implementation of Arbitrary that will allow us to use the Set type in QuickCheck:

instance (Arbitrary a) => Arbitrary (Set a) where
    arbitrary = do
                list <- arbitrary
                return $ Set list

Note that this time we have to have the typeclass (Arbitrary a) in the definition. With this addition we can create Sets of anything that provides implementation for Arbitrary, e.g. Set Int, Set String and Set Point!

*QCSamples> sample $ (arbitrary :: Gen (Set Int))
{}
{}
{}
{}
{-32,1,-28,-14,-22,-13}
{-12,36,6,-50,-36,-28,-49,-7}
{-98}
{183,-29,191,179,-152,94,-225,-19,28}
{-82,-562,385,-146,187,627,-825,-30,227}
{1184,-780,-1787,1720,-1204,-1382,450}
{-128,2874,-636,845,3477,699,2989,-3449,-2221,3587,1107,1365,-3792,357,-487}
*QCSamples> 
*QCSamples> sample $ (arbitrary :: Gen (Set Point))
{}
{{2,-2},{-1,-1}}
{}
{}
{{3,-27}}
{{0,-28},{-61,19},{-52,-43},{41,8},{-43,-34},{-9,-33},{63,-62},{49,16},{-3,-3},{56,4}}
{{48,76},{-122,82}}
{{238,-28},{243,122},{3,189},{-79,-104}}
{{56,-862},{947,-712},{17,-566},{-229,-652},{836,568}}
{{-1883,-794},{1995,-1934}}
{{1265,-1564},{837,3327},{3197,-2594},{-2486,-1393}}

Generating Permutations and Derangements using Haskell

Implementing functions that generate permutations and derangements is like a baptism ritual for every Haskell newbie. So, let’s try to give implementations for the following four functions:

  • isPermutation – checks if a given list is a permutation of another
  • perms – generates the permutations of a given list
  • isDerangement – checks if a given list is a derangement of another
  • deran – generates the derangements of the list [0..n]

Task 1. Create a isPermutation function that takes two lists and returns True if the arguments are permutations of each other.

Solution 1. The function should take two lists of type a and return a Boolean, so its declaration should look like [a] -> [a] -> Bool. One implementation will be to iterate over the elements of the first list and check if each of these appears in the second list. In pseudo code the recursion will look like this:

  1. Take the first element in arg1
  2. If it does not exist, return False. If it exists in arg2, delete it.
  3. Apply steps 1 and 2 for the all but the first elements in arg1 and the rest of the elements in arg2

Note that if arg1 is a permutation of arg2 the two lists should have the same length each time we compare them.

isPermutation :: Eq a => [a] -> [a] -> Bool
isPermutation [] [] = True
isPermutation xs (y:ys) | length xs /= length (y:ys) = False
                        | otherwise = isPermutation (delete y xs) ys

Task 2. Create a function perms that takes a list with no duplicate elements and generates all permutations of that list.

Solution 2. The function has one parameter of type list and returns a list of lists, so its declaration should be [a] -> [[a]]. The suggested implementation uses list comprehension to iterate over each of the elements of the list and recursion to append the rest of the elements.

perms :: Eq a => [a] -> [[a]]
perms [] = [[]]
perms xs = [ i:j | i <- xs, j <- perms $ delete i xs ]

Task 3. Create a function isDerangement that takes two lists and checks if the second is a derangement of the first.

Solution 3. The function takes two lists and returns a Boolean, so its declaration should be [a] -> [a] -> Bool. The implementation below ensures that the two lists are permutations and applies additional constraint using the index helper function.

isDerangement :: Eq a => [a] -> [a] -> Bool
isDerangement [] [] = True
isDerangement xs ys = and [ x `elem` ys && (index x xs /= index x ys) | x <- xs ] where
      index n (x:xs) | n == x = 0
                     | otherwise = 1 + index n xs

Task 4. Create a function derangements that generates a list of all derangements of the list [0..n]

Solution 4. The function takes a single integer value and returns a list of lists of integers, so its declaration should be Int -> [[Int]]. The following example uses the perms and isDerangement functions and filters all generated permutations for which the isDerangement function returns True.

deran :: Int -> [[Int]]
deran n = filter (\ p -> isDerangement p [0..n-1]) (perms [0..n-1])