DEV Community

soriyeak
soriyeak

Posted on

Extensible Record in Haskell using Vinyl for Noob

In this tutorial, I'm going to show how to use vinyl to create an extensible record within haskell.

This tutorials aim for those who area already familiar with haskell, but cannot figure out how to use vinyl.

We are going to use javascript object/typescript interface as comparison.

Note

  • We are using stack lts-17.1

Setting up the project

  • Using stack new learn-vinyl to create a new project.

  • Add these library to your package.yaml: vinyl, microlens

  • In Lib.hs, add this language extensions

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-} 
Enter fullscreen mode Exit fullscreen mode
  • Add these imports:
import Data.Vinyl
import Data.Vinyl.Syntax ()
import Lens.Micro
import Data.Text
Enter fullscreen mode Exit fullscreen mode

Defining a Record

Let's define a record Person:

type Person = FieldRec
  '[ "name" ::: Text
   , "age" ::: Int
   , "is_single" ::: Bool
   ]
Enter fullscreen mode Exit fullscreen mode

this is equivalent to this typescript version:

type Person = {
  name: string,
  age: number,
  is_single: boolean
}
Enter fullscreen mode Exit fullscreen mode

Constructing the record

To construct a record of type Person, we do this:

marcus :: Person
marcus =
      #name =:= "Marcus"
  <+> #age =:= 58
  <+> #is_single =:= False
Enter fullscreen mode Exit fullscreen mode

Typescript version:

let marcus : Person = 
  {
    name: "Marcus", 
    age: 58, 
    is_single: false
  }
Enter fullscreen mode Exit fullscreen mode

Warning: vinyl record field takes order into the matter, so if you put the wrong order, it will causes the type error.

Example:

bad_record :: Person
bad_record =
      #age =:= 58
  <+> #name =:= "Marcus"
  <+> #is_single =:= False
Enter fullscreen mode Exit fullscreen mode

This is not good, luckily we have a function to re-order the field for us, by using rcast:

marcus2 :: Person
marcus2 = rcast $
      #age =:= (58 :: Int)
  <+> #name =:= ("Marcus" :: Text)
  <+> #is_single =:= False

Enter fullscreen mode Exit fullscreen mode

One bad thing is that, you have to explicitly add the type for some fields.

Accessing the field

To access the field of a record, we can use (^.) operators in microlens:

run :: IO ()
run = do
  print (marcus ^. #name)
Enter fullscreen mode Exit fullscreen mode

TS version:

console.log(marcus.name)
Enter fullscreen mode Exit fullscreen mode

Setting the field of a record

run :: IO ()
run = do
  let updated_marcus = marcus & #name .~ "Aurelius"
  print (updated_marcus ^. #name)
Enter fullscreen mode Exit fullscreen mode

Typescript version:

marcus.name = "Aurelius"
console.log(marcus)
Enter fullscreen mode Exit fullscreen mode

Nested Record

Constructing

To construct a nested record, we add this:

type Empire = FieldRec
  '[ "king" ::: Person
   , "country" ::: Text
   ]

rome :: Empire
rome = 
      #king =:= marcus
  <+> #country =:= "Italy"
Enter fullscreen mode Exit fullscreen mode

Accessing nested field

run :: IO ()
run = do
  print (rome ^. #king . #name)
Enter fullscreen mode Exit fullscreen mode

Typescript version:

console.log(rome.king.name)
Enter fullscreen mode Exit fullscreen mode

Setting nested field

run :: IO ()
run = do
  let updated_rome = rome & #king . #name .~ "Aurelius"
  print (updated_rome ^. #king . #name)
Enter fullscreen mode Exit fullscreen mode
rome.king.name = "Aurelius"
console.log(rome)
Enter fullscreen mode Exit fullscreen mode

Conclusion

vinyl is a very powerful library, yet it lags a simple tutorial. That is the reason why I create this tutorial.

In the future, we will talk about record subset, combining record, and more.

Full source code:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}

module Lib
    ( run
    ) where

import Data.Vinyl
import Data.Vinyl.Syntax ()
import Lens.Micro
import Data.Text

type Person = FieldRec
  '[ "name" ::: Text
   , "age" ::: Int
   , "is_single" ::: Bool
   ]

type Empire = FieldRec
  '[ "king" ::: Person
   , "country" ::: Text
   ]

marcus :: Person
marcus =
      #name =:= "Marcus"
  <+> #age =:= 58
  <+> #is_single =:= False

-- bad_record :: Person
-- bad_record =
--       #age =:= 58
--   <+> #name =:= "Marcus"
--   <+> #is_single =:= False

marcus2 :: Person
marcus2 = rcast $
      #age =:= (58 :: Int)
  <+> #name =:= ("Marcus" :: Text)
  <+> #is_single =:= False

rome :: Empire
rome =
      #king =:= marcus
  <+> #country =:= "Italy"


run :: IO ()
run = do
  print (marcus ^. #name)

  let updated_marcus = marcus & #name .~ "Aurelius"
  print (updated_marcus ^. #name)

  -- Nested
  print (rome ^. #king . #name)

  let updated_rome = rome & #king . #name .~ "Aurelius"
  print (updated_rome ^. #king . #name)

Enter fullscreen mode Exit fullscreen mode

Top comments (0)