type aware setter lens - Haskell

Welcome to the Functional Programming Zulip Chat Archive. You can join the chat here.

James King

I'm working on an idea to stitch together lens-aeson and higgledy in order to construct types from partial data that we parse from aeson. Right now I have, as an example:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeApplications #-}

module Lib where

import Control.Lens hiding ((.=))
import Data.Aeson
import Data.Aeson.Lens
import Data.Functor.Const
import Data.Functor.Identity
import Data.Generic.HKD
import Data.Maybe
import Data.Monoid
import GHC.Generics

data Department
  = Sales
  | Engineering
  | Management
  | Support
  deriving (Eq, Generic, Show)

instance ToJSON Department
instance FromJSON Department

data Employee
  = Employee
  { _employeeFirstName  :: String
  , _employeeLastName   :: String
  , _employeeNumber     :: Int
  , _employeeDepartment :: Department
  }
  deriving (Eq, Generic, Show)

type EmployeeF f = HKD Employee f
type PartialEmployee = EmployeeF Last

parseEmployee :: Value -> PartialEmployee
parseEmployee v =
  mempty
  & field @"_employeeFirstName" .~ (v ^. key "firstName" . _JSON)

What I'm trying to figure out is how to get parseEmployee to have a type error if the lens focused on by the setter returns a value of the wrong type. For example:

𝝀 let empObj = object [ "firstName" .= 123, "somethingElse" .= 123 ]
𝝀 safeParseEmployee empObj
Employee {_employeeFirstName = Last {getLast = Nothing}, _employeeLastName = Last {getLast = Nothing}, _employeeNumber = Last {getLast = Nothing}, _employeeDepartment = Last {getLast = Nothing}}

It would be better if, as aeson would, we have this become a type error. :thinking:

James King

Maybe a @Chris Penner question. ;)

James King

No progress yet on getting a type error to show up but I have been able to be more specific by using the right prism, _String which actually returns Text... a bit of a misnomer.

James King

Now the trick seems to be finding a way to focus the prism that lets me return into Last instead of Maybe... I presently have:

o ^. key "firstName" ^? _String

which isn't quite right... progress!

James King

Actually that does solve the type error issue. Now I just have to figure out how to get a Value into Last which seems to require a Monoid instance. :thinking:

James King

It only seems to mostly work if I use the _JSON prism -- _String and _Integer etc cause problems... the consequence is that if the type of the value in the parsed Value doesn't match up with what our record expects we simply get Nothing

Chris Penner

But yeah; should be able to:

Last (o ^? key "firstName" . _String)
Chris Penner

(Make sure you're using Data.Monoid (Last) instead of the Semigroup version

Chris Penner

Let me know if that's not what you're looking for :)

James King

If I try to use _String it throws a type match error:

    • Couldn't match type ‘Last Text’ with ‘Text’
      Expected type: Getting (Last Text) Value (Last Text)
        Actual type: (Text -> Const (Last Text) Text)
                     -> Value -> Const (Last Text) Value
    • In the second argument of ‘(^.)’, namely ‘key "firstName" . _String’
      In the second argument of ‘(.~)’, namely
        ‘(o ^. key "firstName" . _String)’
      In the second argument of ‘(&)’, namely
        ‘field @"_employeeFirstName" .~ (o ^. key "firstName" . _String)’
   |
33 |   & field @"_employeeFirstName" .~ (o ^. key "firstName" . _String)
   |                                           ^^^^^^^^^^^^^^^^^^^^

But _JSON compiles fine... the consequence is that if there is a type mismatch I get a value of Nothing for the field at run time.

James King

I guess I'd have to handle writing my own type validation.

James King

Something that would let me say, "You gave me an Int when I was expecting a String while parsing the value of the key "foo""

Jack Henahan

@James King It looks like it's mainly complaining about the lack of a Last in there. Am I reading it wrong?

James King

@Jack Henahan That's what it says, though as I've mentioned I'm not sure how to stuff the result of view into the Last

However, it seems like aeson can figure out the generic instance for type MaybeEmployee = EmployeeF Maybe! Which means I we can use decodeEither to recover those type mismatch errors instead of rolling our own parsing with aeson-lens.

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeSynonymInstances #-}

module Lib where

import Control.Lens hiding ((.=))
import Data.Aeson
import Data.Aeson.Lens
import Data.Functor.Const
import Data.Functor.Identity
import Data.Generic.HKD
import Data.Maybe
import Data.Monoid
import Data.Text (Text())
import GHC.Generics

data Department
  = Sales
  | Engineering
  | Management
  | Support
  deriving (Eq, Generic, Show)

instance ToJSON Department
instance FromJSON Department

data Employee
  = Employee
  { _employeeFirstName  :: Text
  , _employeeLastName   :: Text
  , _employeeNumber     :: Int
  , _employeeDepartment :: Department
  }
  deriving (Eq, Generic, Show)

type EmployeeF f = HKD Employee f
type PartialEmployee = EmployeeF Last
type MaybeEmployee = EmployeeF Maybe

instance ToJSON PartialEmployee
instance FromJSON PartialEmployee

instance ToJSON MaybeEmployee
instance FromJSON MaybeEmployee
Jack Henahan

HKD is truly wonderful magic

James King

It's pretty great. I deal with a lot of partial data on my inputs and having HKD is like having super powers.