Hi Anthony,

Please see my comments below.

On 16 February 2017 at 02:31, Anthony Clayden <anthony_clayden@clear.net.nz> wrote:
> On Tue, 14 Feb 2017 at 18:50, Harendra Kumar said:

Hi Harendra. I believe rawr builds on some of the work in
'overloaded records'.

I am aware of the ghc "overloaded records" proposal. rawr provides anonymous extensible records using the overloaded labels feature of ghc 8. Records can be merged or partitioned. I believe, the key difference between "overloaded records" and rawr is that the latter provides extensible records while the former does not. Though overloaded records can match a record based on the fields it contains.
 

It's not clear what you're trying to do.
Do you need anonymous/extensible records?

I am trying to write a program which provides a friendly high level DSL to the user. I want a pure function like API but instead of passing positional parameters I want the user to be able to specify arguments based on keywords and be able to skip any optional arguments. Something like the following, name is mandatory and email is optional:

maintainer  (#name  := "Harendra Kumar",  #email := "xyz@gmail.com")

I can achieve this using rawr. The argument to the function is an anonymous record and we can pattern match partially using the mandatory fields in the record to statically check that those fields are present. The optional fields are then supplied by applying the user supplied record on a default record. Here is a full working program for this example (you will need the latest rawr from github):

{-# LANGUAGE FlexibleContexts    #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE ScopedTypeVariables#-}
{-# LANGUAGE TypeOperators#-}

import Data.Rawr

pr t = print $
    case (R t) of
        r@(P (_ := name :: "name" := String)) -> R (#email := "default@gmail.com") :<= r

main = do
    -- both name and email are specified by the user.
    pr (#name  := "Harendra Kumar",  #email := "xyz@gmail.com")

    -- only name is supplied by the user, the default value of the optional field "email" will be used
    pr (#name  := "Harendra Kumar")

    -- This will not compile since name is a mandatory field
    -- pr  (#email := "xyz@gmail.com")


I am pretty sure that I am not writing python code in Haskell I was only trying to say that this is a pretty useful feature in python and I guess in some other imperative languages too. It allows you to write self documenting code where necessary. It will be nice if we have a way to achieve something like this.

 
>Like

    data MyR = MyR { a :: Int, b :: String };

If you want default values:

    myRdef = MyR{ a = 0 };  -- don't have to give b

Then bind some value, to incorp defaults.

    r = myRdef { b = "hello" };   -- takes the defult for a

 
This is the first approach that I tried, this is commonly used in many libraries. The only drawback with this is that I cannot enforce mandatory/optional fields statically. All fields are optional in this case.

-harendra