Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

How can I deal with “typedef”-style data types with a minimum of boilerplate?

Tags:

haskell

I defined a custom data type that contains a single field:

import Data.Set (Set)

data GraphEdge a = GraphEdge (Set a)

Defining my own type feels more semantically correct but it leads to a lot of boilerplate in my functions. Any time I want to use the built-in Set functions I have to unwrap the inner set and later rewrap it:

import Data.Set (map)

modifyItemsSomehow :: Ord a => GraphEdge a -> GraphEdge a
modifyItemsSomehow (GraphEdge items) = GraphEdge $ Set.map someFunction items

This could be improved slightly by making it a record, like

import Data.Set (Set, map)

data GraphEdge a = GraphEdge { unGraphEdge :: Set a }

modifyItemsSomehow = GraphEdge . map someFunction . unGraphEdge

but this still feels far from ideal. What is the most idiomatic way to handle this kind of boilerplate when dealing with a user-defined data type that consists of a single field?

like image 638
bdesham Avatar asked Jan 12 '16 03:01

bdesham


1 Answers

Before anything else, you should make sure to use newtype for single-field single-constructor types. data introduces runtime overhead and extra laziness, and prevents us from using the first two of the following techniques.

First, you can use GeneralizedNewtypeDeriving when possible:

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

newtype Foo a = Foo a deriving (Eq, Show, Ord, Num)

foo :: Foo Int
foo = 0

bar :: Foo Int
bar = foo * 120

Second, you can use coerce to generally convert between newtype wrappings:

import Data.Coerce

newtype Foo a = Foo a
newtype Bar a = Bar a

a :: [(Foo (Bar Int), Foo ())]
a = [(Foo (Bar 0), Foo ())]

b :: [(Int, ())]
b = coerce a

Third, you can use iso-s from lens to concisely move operations over/under newtype constructors.

{-# LANGUAGE TemplateHaskell #-}

import Data.Set (Set)
import qualified Data.Set as Set
import Control.Lens

newtype GraphEdge a = GraphEdge (Set a)
makePrisms ''GraphEdge

modifyItemsSomehow :: Ord a => GraphEdge a -> GraphEdge a
modifyItemsSomehow = _GraphEdge %~ Set.map someFunction
like image 63
András Kovács Avatar answered Sep 24 '22 17:09

András Kovács