Unifying Operations on Two Data Types via a Typeclas

Hi folks,

I have two data types that differ in only their Applicative instance, just to play around with a data type that does not accumulate errors and one that does.

The source code can be found here, but for the purposes of this post, what I would like to focus on is the following two functions:

validateResult :: RawData -> Result [CustomError] ValidData
validateResult RawData {..} =
  ValidData
    <$> expect "fieldOne"   fieldOne
    <*> expect "fieldTwo"   fieldTwo
    <*> expect "fieldThree" fieldThree
 where
  expect :: String -> Maybe a -> Result [CustomError] a
  expect field Nothing  = Result . Left $ [CustomError field]
  expect field (Just a) = Result $ Right a


validateOperation :: RawData -> Operation [CustomError] ValidData
validateOperation RawData {..} =
  ValidData
    <$> expect "fieldOne"   fieldOne
    <*> expect "fieldTwo"   fieldTwo
    <*> expect "fieldThree" fieldThree
 where
  expect :: String -> Maybe a -> Operation [CustomError] a
  expect field Nothing  = Operation . Left $ [CustomError field]
  expect field (Just a) = Operation $ Right a

The two functions are the same. The only thing that differs is the data constructor used to create the success and failure conditions in expect. Therefore, I imagine that there is a way to create a function such as:

validate :: (Applicative v, Validate v) => RawData -> v ValidData
validate RawData {..} =
  ValidData
    <$> expect "fieldOne"   fieldOne
    <*> expect "fieldTwo"   fieldTwo
    <*> expect "fieldThree" fieldThree
 where
  expect field Nothing  = refute [CustomError field]
  expect field (Just a) = success a

I have tried to do this (as you can see in the commented-out code in the source file), but it leads to a host of type errors, and I was wondering if someone could point me in the right direction.

I understand that this is a very open-ended question, but I don’t know how to ask it in a more direct manner.

I didn’t test it but this compiles for me. However I dunno if it does what you want. I added a type parameter to Validate for the error type, and used functional dependencies so that v specifies it.

It might make sense if you have Applicative v be a superclass of Validate like in the MonadX classes.

{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}

newtype Result e a = Result
  { unResult :: Either e a
  }
  deriving newtype (Functor, Applicative)
  deriving stock (Show)

data RawData = RawData
  { fieldOne   :: Maybe Int
  , fieldTwo   :: Maybe Char
  , fieldThree :: Maybe Bool
  }

data ValidData = ValidData
  { fOne   :: Int
  , fTwo   :: Char
  , fThree :: Bool
  }
  deriving stock Show

newtype CustomError = CustomError String deriving Show

class Validate e v | v -> e where
  success :: a -> v a
  refute :: e -> v a

instance Validate e (Result e) where
  success :: a -> Result e a
  success = Result . Right

  refute :: e -> Result e a
  refute = Result . Left

validate :: (Applicative v, Validate [CustomError] v) => RawData -> v ValidData
validate RawData {..} =
  ValidData
    <$> expect "fieldOne"   fieldOne
    <*> expect "fieldTwo"   fieldTwo
    <*> expect "fieldThree" fieldThree
 where
  expect field Nothing  = refute [CustomError field]
  expect field (Just a) = success a

This worked great. Once I used functional dependencies, the rest of it became clear. I have a fully functioning version here, for those interested.

Thank you @eddiemundo!