Deriving Eq and Show for an ADT that contains fields that can't have Eq or Show - haskell

I'd like to be able to derive Eq and Show for an ADT that contains multiple fields. One of them is a function field. When doing Show, I'd like it to display something bogus, like e.g. "<function>"; when doing Eq, I'd like it to ignore that field. How can I best do this without hand-writing a full instance for Show and Eq?
I don't want to wrap the function field inside a newtype and write my own Eq and Show for that - it would be too bothersome to use like that.

One way you can get proper Eq and Show instances is to, instead of hard-coding that function field, make it a type parameter and provide a function that just “erases” that field. I.e., if you have
data Foo = Foo
{ fooI :: Int
, fooF :: Int -> Int }
you change it to
data Foo' f = Foo
{ _fooI :: Int
, _fooF :: f }
deriving (Eq, Show)
type Foo = Foo' (Int -> Int)
eraseFn :: Foo -> Foo' ()
eraseFn foo = foo{ fooF = () }
Then, Foo will still not be Eq- or Showable (which after all it shouldn't be), but to make a Foo value showable you can just wrap it in eraseFn.

Typically what I do in this circumstance is exactly what you say you don’t want to do, namely, wrap the function in a newtype and provide a Show for that:
data T1
{ f :: X -> Y
, xs :: [String]
, ys :: [Bool]
}
data T2
{ f :: OpaqueFunction X Y
, xs :: [String]
, ys :: [Bool]
}
deriving (Show)
newtype OpaqueFunction a b = OpaqueFunction (a -> b)
instance Show (OpaqueFunction a b) where
show = const "<function>"
If you don’t want to do that, you can instead make the function a type parameter, and substitute it out when Showing the type:
data T3' a
{ f :: a
, xs :: [String]
, ys :: [Bool]
}
deriving (Functor, Show)
newtype T3 = T3 (T3' (X -> Y))
data Opaque = Opaque
instance Show Opaque where
show = const "..."
instance Show T3 where
show (T3 t) = show (Opaque <$ t)
Or I’ll refactor my data type to derive Show only for the parts I want to be Showable by default, and override the other parts:
data T4 = T4
{ f :: X -> Y
, xys :: T4' -- Move the other fields into another type.
}
instance Show T4 where
show (T4 f xys) = "T4 <function> " <> show xys
data T4' = T4'
{ xs :: [String]
, ys :: [Bool]
}
deriving (Show) -- Derive ‘Show’ for the showable fields.
Or if my type is small, I’ll use a newtype instead of data, and derive Show via something like OpaqueFunction:
{-# LANGUAGE DerivingVia #-}
newtype T5 = T5 (X -> Y, [String], [Bool])
deriving (Show) via (OpaqueFunction X Y, [String], [Bool])
You can use the iso-deriving package to do this for data types using lenses if you care about keeping the field names / record accessors.
As for Eq (or Ord), it’s not a good idea to have an instance that equates values that can be observably distinguished in some way, since some code will treat them as identical and other code will not, and now you’re forced to care about stability: in some circumstance where I have a == b, should I pick a or b? This is why substitutability is a law for Eq: forall x y f. (x == y) ==> (f x == f y) if f is a “public” function that upholds the invariants of the type of x and y (although floating-point also violates this). A better choice is something like T4 above, having equality only for the parts of a type that can satisfy the laws, or explicitly using comparison modulo some function at use sites, e.g., comparing someField.

The module Text.Show.Functions in base provides a show instance for functions that displays <function>. To use it, just:
import Text.Show.Functions
It just defines an instance something like:
instance Show (a -> b) where
show _ = "<function>"
Similarly, you can define your own Eq instance:
import Text.Show.Functions
instance Eq (a -> b) where
-- all functions are equal...
-- ...though some are more equal than others
_ == _ = True
data Foo = Foo Int Double (Int -> Int) deriving (Show, Eq)
main = do
print $ Foo 1 2.0 (+1)
print $ Foo 1 2.0 (+1) == Foo 1 2.0 (+2) -- is True
This will be an orphan instance, so you'll get a warning with -Wall.
Obviously, these instances will apply to all functions. You can write instances for a more specialized function type (e.g., only for Int -> String, if that's the type of the function field in your data type), but there is no way to simultaneously (1) use the built-in Eq and Show deriving mechanisms to derive instances for your datatype, (2) not introduce a newtype wrapper for the function field (or some other type polymorphism as mentioned in the other answers), and (3) only have the function instances apply to the function field of your data type and not other function values of the same type.
If you really want to limit applicability of the custom function instances without a newtype wrapper, you'd probably need to build your own generics-based solution, which wouldn't make much sense unless you wanted to do this for a lot of data types. If you go this route, then the Generics.Deriving.Show and Generics.Deriving.Eq modules in generic-deriving provide templates for these instances which could be modified to treat functions specially, allowing you to derive per-datatype instances using some stub instances something like:
instance Show Foo where showsPrec = myGenericShowsPrec
instance Eq Foo where (==) = myGenericEquality

I proposed an idea for adding annotations to fields via fields, that allows operating on behaviour of individual fields.
data A = A
{ a :: Int
, b :: Int
, c :: Int -> Int via Ignore (Int->Int)
}
deriving
stock GHC.Generic
deriving (Eq, Show)
via Generically A -- assuming Eq (Generically A)
-- Show (Generically A)
But this is already possible with the "microsurgery" library, but you might have to write some boilerplate to get it going. Another solution is to write separate behaviour in "sums-of-products style"
data A = A Int Int (Int->Int)
deriving
stock GHC.Generic
deriving
anyclass SOP.Generic
deriving (Eq, Show)
via A <-𝈖-> '[ '[ Int, Int, Ignore (Int->Int) ] ]

Related

The limit set of types with new data like `Tree a`

Exploring and studing type system in Haskell I've found some problems.
1) Let's consider polymorphic type as Binary Tree:
data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving Show
And, for example, I want to limit my considerations only with Tree Int, Tree Bool and Tree Char. Of course, I can make a such new type:
data TreeIWant = T1 (Tree Int) | T2 (Tree Bool) | T3 (Tree Char) deriving Show
But could it possible to make new restricted type (for homogeneous trees) in more elegant (and without new tags like T1,T2,T3) way (perhaps with some advanced type extensions)?
2) Second question is about trees with heterogeneous values. I can do them with usual Haskell, i.e. I can do the new helping type, contained tagged heterogeneous values:
data HeteroValues = H1 Int | H2 Bool | H3 Char deriving Show
and then make tree with values of this type:
type TreeH = Tree HeteroValues
But could it possible to make new type (for heterogeneous trees) in more elegant (and without new tags like H1,H2,H3) way (perhaps with some advanced type extensions)?
I know about heterogeneous list, perhaps it is the same question?
For question #2, it's easy to construct a "restricted" heterogeneous type without explicit tags using a GADT and a type class:
{-# LANGUAGE GADTs #-}
data Thing where
T :: THING a => a -> Thing
class THING a
Now, declare THING instances for the the things you want to allow:
instance THING Int
instance THING Bool
instance THING Char
and you can create Things and lists (or trees) of Things:
> t1 = T 'a' -- Char is okay
> t2 = T "hello" -- but String is not
... type error ...
> tl = [T (42 :: Int), T True, T 'x']
> tt = Branch (Leaf (T 'x')) (Leaf (T False))
>
In terms of the type names in your question, you have:
type HeteroValues = Thing
type TreeH = Tree Thing
You can use the same type class with a new GADT for question #1:
data ThingTree where
TT :: THING a => Tree a -> ThingTree
and you have:
type TreeIWant = ThingTree
and you can do:
> tt1 = TT $ Branch (Leaf 'x') (Leaf 'y')
> tt2 = TT $ Branch (Leaf 'x') (Leaf False)
... type error ...
>
That's all well and good, until you try to use any of the values you've constructed. For example, if you wanted to write a function to extract a Bool from a possibly boolish Thing:
maybeBool :: Thing -> Maybe Bool
maybeBool (T x) = ...
you'd find yourself stuck here. Without a "tag" of some kind, there's no way of determining if x is a Bool, Int, or Char.
Actually, though, you do have an implicit tag available, namely the THING type class dictionary for x. So, you can write:
maybeBool :: Thing -> Maybe Bool
maybeBool (T x) = maybeBool' x
and then implement maybeBool' in your type class:
class THING a where
maybeBool' :: a -> Maybe Bool
instance THING Int where
maybeBool' _ = Nothing
instance THING Bool where
maybeBool' = Just
instance THING Char where
maybeBool' _ = Nothing
and you're golden!
Of course, if you'd used explicit tags:
data Thing = T_Int Int | T_Bool Bool | T_Char Char
then you could skip the type class and write:
maybeBool :: Thing -> Maybe Bool
maybeBool (T_Bool x) = Just x
maybeBool _ = Nothing
In the end, it turns out that the best Haskell representation of an algebraic sum of three types is just an algebraic sum of three types:
data Thing = T_Int Int | T_Bool Bool | T_Char Char
Trying to avoid the need for explicit tags will probably lead to a lot of inelegant boilerplate elsewhere.
Update: As #DanielWagner pointed out in a comment, you can use Data.Typeable in place of this boilerplate (effectively, have GHC generate a lot of boilerplate for you), so you can write:
import Data.Typeable
data Thing where
T :: THING a => a -> Thing
class Typeable a => THING a
instance THING Int
instance THING Bool
instance THING Char
maybeBool :: Thing -> Maybe Bool
maybeBool = cast
This perhaps seems "elegant" at first, but if you try this approach in real code, I think you'll regret losing the ability to pattern match on Thing constructors at usage sites (and so having to substitute chains of casts and/or comparisons of TypeReps).

Deserializing many network messages without using an ad-hoc parser implementation

I have a question pertaining to deserialization. I can envision a solution using Data.Data, Data.Typeable, or with GHC.Generics, but I'm curious if it can be accomplished without generics, SYB, or meta-programming.
Problem Description:
Given a list of [String] that is known to contain the fields of a locally defined algebraic data type, I would like to deserialize the [String] to construct the target data type. I could write a parser to do this, but I'm looking for a generalized solution that will deserialize to an arbitrary number of data types defined within the program without writing a parser for each type. With knowledge of the number and type of value constructors an algebraic type has, it's as simple as performing a read on each string to yield the appropriate values necessary to build up the type. However, I don't want to use generics, reflection, SYB, or meta-programming (unless it's otherwise impossible).
Say I have around 50 types defined similar to this (all simple algebraic types composed of basic primitives (no nested or recursive types, just different combinations and orderings of primitives) :
data NetworkMsg = NetworkMsg { field1 :: Int, field2 :: Int, field3 :: Double}
data NetworkMsg2 = NetworkMsg2 { field1 :: Double, field2 :: Int, field3 :: Double }
I can determine the data-type to be associated with a [String] I've received over the network using a tag id that I parse before each [String].
Possible conjectured solution path:
Since data constructors are first-class values in Haskell, and actually have a type-- Can NetworkMsg constructor be thought of as a function, such as:
NetworkMsg :: Int -> Int -> Double -> NetworkMsg
Could I transform this function into a function on tuples using uncurryN then copy the [String] into a tuple of the same shape the function now takes?
NetworkMsg' :: (Int, Int, Double) -> NetworkMsg
I don't think this would work because I'd need knowledge of the value constructors and type information, which would require Data.Typeable, reflection, or some other metaprogramming technique.
Basically, I'm looking for automatic deserialization of many types without writing type instance declarations or analyzing the type's shape at run-time. If it's not feasible, I'll do it an alternative way.
You are correct in that the constructors are essentially just functions so you can write generic instances for any number of types by just writing instances for the functions. You'll still need to write a separate instance
for all the different numbers of arguments, though.
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
import Text.Read
import Control.Applicative
class FieldParser p r where
parseFields :: p -> [String] -> Maybe r
instance Read a => FieldParser (a -> r) r where
parseFields con [a] = con <$> readMaybe a
parseFields _ _ = Nothing
instance (Read a, Read b) => FieldParser (a -> b -> r) r where
parseFields con [a, b] = con <$> readMaybe a <*> readMaybe b
parseFields _ _ = Nothing
instance (Read a, Read b, Read c) => FieldParser (a -> b -> c -> r) r where
parseFields con [a, b, c] = con <$> readMaybe a <*> readMaybe b <*> readMaybe c
parseFields _ _ = Nothing
{- etc. for as many arguments as you need -}
Now you can use this type class to parse any message based on the constructor as long as the type-checker is able to figure out the resulting message type from context (i.e. it is not able to deduce it simply from the given constructor for these sort of multi-param type class instances).
data Test1 = Test1 {fieldA :: Int} deriving Show
data Test2 = Test2 {fieldB ::Int, fieldC :: Float} deriving Show
test :: String -> [String] -> IO ()
test tag fields = case tag of
"Test1" -> case parseFields Test1 fields of
Just (a :: Test1) -> putStrLn $ "Succesfully parsed " ++ show a
Nothing -> putStrLn "Parse error"
"Test2" -> case parseFields Test2 fields of
Just (a :: Test2) -> putStrLn $ "Succesfully parsed " ++ show a
Nothing -> putStrLn "Parse error"
I'd like to know how exactly you use the message types in the application, though, because having each message as its separate type makes it very difficult to have any sort of generic message handler.
Is there some reason why you don't simply have a single message data type? Such as
data NetworkMsg
= NetworkMsg1 {fieldA :: Int}
| NetworkMsg2 {fieldB :: Int, fieldC :: Float}
Now, while the instances are built in pretty much the same way, you get much better type inference since the result type is always known.
instance Read a => MessageParser (a -> NetworkMsg) where
parseMsg con [a] = con <$> readMaybe a
instance (Read a, Read b) => MessageParser (a -> b -> NetworkMsg) where
parseMsg con [a, b] = con <$> readMaybe a <*> readMaybe b
instance (Read a, Read b, Read c) => MessageParser (a -> b -> c -> NetworkMsg) where
parseMsg con [a, b, c] = con <$> readMaybe a <*> readMaybe b <*> readMaybe c
parseMessage :: String -> [String] -> Maybe NetworkMsg
parseMessage tag fields = case tag of
"NetworkMsg1" -> parseMsg NetworkMsg1 fields
"NetworkMsg2" -> parseMsg NetworkMsg2 fields
_ -> Nothing
I'm also not sure why you want to do type-generic programming specifically without actually using any of the tools meant for generics. GHC.Generics, SYB or Template Haskell is usually the best solution for this kind of problem.

How can I read the metadata of a type at runtime?

I'd like to write a program that prints out some metadata of a Haskell type. Although I know this isn't valid code, the idea is something like:
data Person = Person { name :: String, age :: Int }
metadata :: Type -> String
metadata t = ???
metadata Person -- returns "Person (name,age)"
The important restriction being I don't have an instance of Person, just the type.
I've started looking into Generics & Typeable/Data, but without an instance I'm not sure they'll do what I need. Can anyone point me in the right direction?
Reflection in Haskell works using the Typeable class, which is defined in Data.Typeable and includes the typeOf* method to get a run-time representation of a value's type.
ghci> :m +Data.Typeable
ghci> :t typeOf 'a'
typeOf 'a' :: TypeRep
ghci> typeOf 'a' -- We could use any value of type Char and get the same result
Char -- the `Show` instance of `TypeRep` just returns the name of the type
If you want Typeable to work for your own types, you can have the compiler generate an instance for you with the DeriveDataTypeable extension.
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Typeable
data Person = Person { name :: String, age :: Int } deriving Typeable
You can also write your own instance, but really, no one has the time for that. Apparently you can't - see the comments
You can now use typeOf to grab a run-time representation of your type. We can query information about the type constructor (abbreviated to TyCon) and its type arguments:
-- (undefined :: Person) stands for "some value of type Person".
-- If you have a real Person you can use that too.
-- typeOf does not use the value, only the type
-- (which is known at compile-time; typeOf is dispatched using the normal instance selection rules)
ghci> typeOf (undefined :: Person)
Person
ghci> tyConName $ typeRepTyCon $ typeOf (undefined :: Person)
"Person"
ghci> tyConModule $ typeRepTyCon $ typeOf (undefined :: Person)
"Main"
Data.Typeable also provides a type-safe cast operation which allows you to branch on a value's runtime type, somewhat like C#'s as operator.
f :: Typeable a => a -> String
f x = case (cast x :: Maybe Int) of
Just i -> "I can treat i as an int in this branch " ++ show (i * i)
Nothing -> case (cast x :: Maybe Bool) of
Just b -> "I can treat b as a bool in this branch " ++ if b then "yes" else "no"
Nothing -> "x was of some type other than Int or Bool"
ghci> f True
"I can treat b as a bool in this branch yes"
ghci> f (3 :: Int)
"I can treat i as an int in this branch 9"
Incidentally, a nicer way to write f is to use a GADT enumerating the set of types you expect your function to be called with. This allows us to lose the Maybe (f can never fail!), does a better job of documenting our assumptions, and gives compile-time feedback when we need to change the set of admissible argument types for f. (You can write a class to make Admissible implicit if you like.)
data Admissible a where
AdInt :: Admissible Int
AdBool :: Admissible Bool
f :: Admissible a -> a -> String
f AdInt i = "I can treat i as an int in this branch " ++ show (i * i)
f AdBool b = "I can treat b as a bool in this branch " ++ if b then "yes" else "no"
In reality I probably wouldn't do either of these - I'd just stick f in a class and define instances for Int and Bool.
If you want run-time information about the right-hand side of a type definition, you need to use the entertainingly-named Data.Data, which defines a subclass of Typeable called Data.** GHC can derive Data for you too, with the same extension:
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Typeable
import Data.Data
data Person = Person { name :: String, age :: Int } deriving (Typeable, Data)
Now we can grab a run-time representation of the values of a type, not just the type itself:
ghci> dataTypeOf (undefined :: Person)
DataType {tycon = "Main.Person", datarep = AlgRep [Person]}
ghci> dataTypeConstrs $ dataTypeOf (undefined :: Person)
[Person] -- Person only defines one constructor, called Person
ghci> constrFields $ head $ dataTypeConstrs $ dataTypeOf (undefined :: Person)
["name","age"]
Data.Data is the API for generic programming; if you ever hear people talking about "Scrap Your Boilerplate", this (along with Data.Generics, which builds on Data.Data) is what they mean. For example, you can write a function which converts record types to JSON using reflection on the type's fields.
toJSON :: Data a => a -> String
-- Implementation omitted because it is boring.
-- But you only have to write the boring code once,
-- and it'll be able to serialise any instance of `Data`.
-- It's a good exercise to try to write this function yourself!
* In recent versions of GHC, this API has changed somewhat. Consult the docs.
** Yes, the fully-qualified name of that class is Data.Data.Data.

Get a list of the instances in a type class in Haskell

Is there a way to programmatically get a list of instances of a type class?
It strikes me that the compiler must know this information in order to type check and compile the code, so is there some way to tell the compiler: hey, you know those instances of that class, please put a list of them right here (as strings or whatever some representation of them).
You can generate the instances in scope for a given type class using Template Haskell.
import Language.Haskell.TH
-- get a list of instances
getInstances :: Name -> Q [ClassInstance]
getInstances typ = do
ClassI _ instances <- reify typ
return instances
-- convert the list of instances into an Exp so they can be displayed in GHCi
showInstances :: Name -> Q Exp
showInstances typ = do
ins <- getInstances typ
return . LitE . stringL $ show ins
Running this in GHCi:
*Main> $(showInstances ''Num)
"[ClassInstance {ci_dfun = GHC.Num.$fNumInteger, ci_tvs = [], ci_cxt = [], ci_cls = GHC.Num.Num, ci_tys = [ConT GHC.Integer.Type.Integer]},ClassInstance {ci_dfun = GHC.Num.$fNumInt, ci_tvs = [], ci_cxt = [], ci_cls = GHC.Num.Num, ci_tys = [ConT GHC.Types.Int]},ClassInstance {ci_dfun = GHC.Float.$fNumFloat, ci_tvs = [], ci_cxt = [], ci_cls = GHC.Num.Num, ci_tys = [ConT GHC.Types.Float]},ClassInstance {ci_dfun = GHC.Float.$fNumDouble, ci_tvs = [], ci_cxt = [], ci_cls = GHC.Num.Num, ci_tys = [ConT GHC.Types.Double]}]"
Another useful technique is showing all instances in scope for a given type class using GHCi.
Prelude> :info Num
class (Eq a, Show a) => Num a where
(+) :: a -> a -> a
(*) :: a -> a -> a
(-) :: a -> a -> a
negate :: a -> a
abs :: a -> a
signum :: a -> a
fromInteger :: Integer -> a
-- Defined in GHC.Num
instance Num Integer -- Defined in GHC.Num
instance Num Int -- Defined in GHC.Num
instance Num Float -- Defined in GHC.Float
instance Num Double -- Defined in GHC.Float
Edit: The important thing to know is that the compiler is only aware of type classes in scope in any given module (or at the ghci prompt, etc.). So if you call the showInstances TH function with no imports, you'll only get instances from the Prelude. If you have other modules in scope, e.g. Data.Word, then you'll see all those instances too.
See the template haskell documentation: http://hackage.haskell.org/packages/archive/template-haskell/2.5.0.0/doc/html/Language-Haskell-TH.html
Using reify, you can get an Info record, which for a class includes its list of instances. You can also use isClassInstance and classInstances directly.
This is going to run into a lot of problems as soon as you get instance declarations like
instance Eq a => Eq [a] where
[] == [] = True
(x:xs) == (y:ys) = x == y && xs == ys
_ == _ = False
and
instance (Eq a,Eq b) => Eq (a,b) where
(a1,b1) == (a2,b2) = a1 == a2 && b1 == b2
along with a single concrete instance (e.g. instance Eq Bool).
You'll get an infinite list of instances for Eq - Bool,[Bool],[[Bool]],[[[Bool]]] and so on, (Bool,Bool), ((Bool,Bool),Bool), (((Bool,Bool),Bool),Bool) etcetera, along with various combinations of these such as ([((Bool,[Bool]),Bool)],Bool) and so forth. It's not clear how to represent these in a String; even a list of TypeRep would require some pretty smart enumeration.
The compiler can (try to) deduce whether a type is an instance of Eq for any given type, but it doesn't read in all the instance declarations in scope and then just starts deducing all possible instances, since that will never finish!
The important question is of course, what do you need this for?
I guess, it's not possible. I explain you the implementation of typeclasses (for GHC), from it, you can see, that the compiler has no need to know which types are instance of a typeclass. It only has to know, whether a specific type is instance or not.
A typeclass will be translated into a datatype. As an example, let's take Eq:
class Eq a where
(==),(/=) :: a -> a -> Bool
The typeclass will be translated into a kind of dictionary, containing all its functions:
data Eq a = Eq {
(==) :: a -> a -> Bool,
(/=) :: a -> a -> Bool
}
Each typeclass constraint is then translated into an extra argument containing the dictionary:
elem :: Eq a => a -> [a] -> Bool
elem _ [] = False
elem a (x:xs) | x == a = True
| otherwise = elem a xs
becomes:
elem :: Eq a -> a -> [a] -> Bool
elem _ _ [] = False
elem eq a (x:xs) | (==) eq x a = True
| otherwise = elem eq a xs
The important thing is, that the dictionary will be passed at runtime. Imagine, your project contains many modules. GHC doesn't have to check all the modules for instances, it just has to look up, whether an instance is defined anywhere.
But if you have the source available, I guess an old-style grep for the instances would be sufficient.
It is not possible to automatically do this for existing classes. For your own class and instances thereof you could do it. You would need to declare everything via Template Haskell (or perhaps the quasi-quoting) and it would automatically generate some strange data structure that encodes the declared instances. Defining the strange data structure and making Template Haskell do this are details left to whomever has a use case for them.
Perhaps you could add some Template Haskell or other magic to your build to include all the source files as text available at run-time (c.f. program quine). Then your program would 'grep itself'...

Haskell record syntax and type classes

Suppose that I have two data types Foo and Bar. Foo has fields x and y. Bar has fields x and z. I want to be able to write a function that takes either a Foo or a Bar as a parameter, extracts the x value, performs some calculation on it, and then returns a new Foo or Bar with the x value set accordingly.
Here is one approach:
class HasX a where
getX :: a -> Int
setX :: a -> Int -> a
data Foo = Foo Int Int deriving Show
instance HasX Foo where
getX (Foo x _) = x
setX (Foo _ y) val = Foo val y
getY (Foo _ z) = z
setY (Foo x _) val = Foo x val
data Bar = Bar Int Int deriving Show
instance HasX Bar where
getX (Bar x _) = x
setX (Bar _ z) val = Bar val z
getZ (Bar _ z) = z
setZ (Bar x _) val = Bar x val
modifyX :: (HasX a) => a -> a
modifyX hasX = setX hasX $ getX hasX + 5
The problem is that all those getters and setters are painful to write, especially if I replace Foo and Bar with real-world data types that have lots of fields.
Haskell's record syntax gives a much nicer way of defining these records. But, if I try to define the records like this
data Foo = Foo {x :: Int, y :: Int} deriving Show
data Bar = Foo {x :: Int, z :: Int} deriving Show
I'll get an error saying that x is defined multiple times. And, I'm not seeing any way to make these part of a type class so that I can pass them to modifyX.
Is there a nice clean way of solving this problem, or am I stuck with defining my own getters and setters? Put another way, is there a way of connecting the functions created by record syntax up with type classes (both the getters and setters)?
EDIT
Here's the real problem I'm trying to solve. I'm writing a series of related programs that all use System.Console.GetOpt to parse their command-line options. There will be a lot of command-line options that are common across these programs, but some of the programs may have extra options. I'd like each program to be able to define a record containing all of its option values. I then start with a default record value that is then transformed through a StateT monad and GetOpt to get a final record reflecting the command-line arguments. For a single program, this approach works really well, but I'm trying to find a way to re-use code across all of the programs.
You want extensible records which, I gather, is one of the most talked about topics in Haskell. It appears that there is not currently much consensus on how to implement it.
In your case it seems like maybe instead of an ordinary record you could use a heterogeneous list like those implemented in HList.
Then again, it seems you only have two levels here: common and program. So maybe you should just define a common record type for the common options and a program-specific record type for each program, and use StateT on a tuple of those types. For the common stuff you can add aliases that compose fst with the common accessors so it's invisible to callers.
You could use code such as
data Foo = Foo { fooX :: Int, fooY :: Int } deriving (Show)
data Bar = Bar { barX :: Int, barZ :: Int } deriving (Show)
instance HasX Foo where
getX = fooX
setX r x' = r { fooX = x' }
instance HasX Bar where
getX = barX
setX r x' = r { barX = x' }
What are you modeling in your code? If we knew more about the problem, we could suggest something less awkward than this object-oriented design shoehorned into a functional language.
Seems to me like a job for generics. If you could tag your Int with different newtypes, then you would be able to write (with uniplate, module PlateData):
data Foo = Foo Something Another deriving (Data,Typeable)
data Bar = Bar Another Thing deriving (Data, Typerable)
data Opts = F Foo | B Bar
newtype Something = S Int
newtype Another = A Int
newtype Thing = T Int
getAnothers opts = [ x | A x <- universeBi opts ]
This would extract all Another's from anywhere inside the Opts.
Modification is possible as well.
If you make the types instances of Foldable you get a toList function that you can use as the basis of your accessor.
If Foldable doesn't by you anything, then maybe the right approach is to define the interface you want as a type class and figure out a good way to autogenerate the derived values.
Perhaps by deriving from doing
deriving(Data)
you could use gmap combinators to base your access off.

Resources