Objects of multiple datatypes - object

I need to implement a chess game for a school assignment, and you have to make an interface that will work for other games on the same board. So, you have to implement chess pieces, but also pieces for other games.
I tried to do this:
data ChessPiece = King | Queen | Knight | Rook | Bishop | Pawn deriving (Enum, Eq, Show)
data Piece = ChessPiece | OtherGamePiece deriving (Enum, Eq, Show)
data ColoredPiece = White Piece | Black Piece
data Board = Board { boardData :: (Array Pos (Maybe ColoredPiece)) }
Then I try to load the begin f the chess game with:
beginBoard = Board (listArray (Pos 0 0, Pos 7 7) (pieces White ++ pawns White ++ space ++ pawns Black ++ pieces Black)) where
pieces :: (Piece -> ColoredPiece) -> [Maybe ColoredPiece]
pieces f = [Just (f Rook), Just (f Knight), Just (f Bishop), Just (f Queen), Just (f King), Just (f Bishop), Just (f Knight), Just (f Rook)]
pawns :: (Piece -> ColoredPiece) -> [Maybe ColoredPiece]
pawns f = (take 8 (repeat (Just (f Pawn))))
space = take 32 (repeat Nothing)
And I get the error "Couldn't match expected type Piece' with actual typeChessPiece'
In the first argument of f', namelyRook'
In the first argument of Just', namely(f Rook)'
In the expression: Just (f Rook)"
So, I've the feeling that the ChessPiece needs to be 'casted' to a (regular) Piece somehow.
(I know, I am using terms from imperative programming, but I hope that I make myself clear here, I will be happy to make my question clearer if needed).
Is the construct that I'm trying to make possible? (sort of like a class structure from OO languages, but then applied to datatypes, where one datatype is a sub-datatype from the other, and an object can be two datatypes at the same time. For example a Rook is a ChessPiece and therefore a Piece)
What am I doing wrong? Any suggestions on how to implement the structure I need?

What you are after is normally referred to as sub-typing. Most OO languages achieve sub-typing using sub-classes.
Haskell, however, is decidedly not an OO language; in fact, it does not really have any sort of sub-typing at all. Happily, you can usually achieve much the same effect using "parametric polymorphism". Now, "parametric polymorphism" is a scary-sounding term! What does it mean?
In fact, it has a very simple meaning: you can write code that works for all (concrete) types. The Maybe type, which you already know how to use, is a great example here. The type is defined as follows:
data Maybe a = Just a | Nothing
note how it is written as Maybe a rather than just Maybe; the a is a type variable. This means that, when you go to use Maybe, you can use it with any type. You can have a Maybe Int, a Maybe Bool, a Maybe [Int] and even a Maybe (Maybe (Maybe (Maybe Double))).
You can use this approach to define your board. For basic board functions, you do not care about what "piece" is actually on the board--there are some actions that make sense for any piece. On the other hand, if you do care about the type of the piece, you will be caring about what the type is exactly, because the rules for each game are going to be different.
This means that you can define your board with some type variable for pieces. Right now, your board representation looks like this:
data Board = Board {boardData :: Array Pos (Maybe ColoredPiece)}
since you want to generalize the board to any sort of piece, you need to add a type variable instead of specifying ColoredPiece:
data Board p = Board {boardData :: Array Pos p}
now you've defined a Board type for any piece type you could possibly imagine!
So, to use this board representation for chess pieces, you need to pass the type of the piece to your new Board type. This will look something like this:
type ChessBoard = Board ColoredPiece
(For reference, type just creates a synonym--now writing ChessBoard is completely equivalent to writing Board ColoredPiece.)
So now, whenever you have a chess board, use your new ChessBoard type.
Additionally, you can write some useful functions that work on any board. For example, let's imagine all you want to do is get a list of the pieces. The type of this function would then be:
listPieces :: Board p -> [p]
You can write a whole bunch of other similar functions that don't care about the actual piece by using type variables like p in your function types. This function will now work for any board you give it, including a Board ColoredPiece, otherwise know as ChessBoard.
In summary: you want to write your Board representation polymorphically. This lets you achieve the same effect as you wanted to try with sub-typing.

Tikhon's solution is the way to go. FYI though, note the difference between a type constructor and a data constructor. Right here, for example:
data ChessPiece = King | Queen | Knight | Rook | Bishop | Pawn deriving (Enum, Eq, Show)
data Piece = ChessPiece | OtherGamePiece deriving (Enum, Eq, Show)
This won't work because you're defining a type constructor called ChessPiece in the first line and a data constructor called ChessPiece in the other, and these aren't the same thing. The type constructor says something like: "a ChessPiece type can be a King, or a Queen, or a..." while the data constructor just creates generic data (that also happens to be called ChessPiece).
What you can do is redefine the first data constructor for the Piece type; some generic data called ChessPiece that carries some information about the type ChessPiece under the hood. The following typechecks:
data ChessPiece = King | Queen | Knight | Rook | Bishop | Pawn deriving (Enum, Eq, Show)
data Piece = ChessPiece ChessPiece | OtherGamePiece -- note the change
data ColoredPiece = White Piece | Black Piece
and you could alter your functions like so:
pieces :: (Piece -> ColoredPiece) -> [Maybe ColoredPiece]
pieces f = [Just (f (ChessPiece Rook)), Just (f (ChessPiece Knight)), Just (f (ChessPiece Bishop)), Just (f (ChessPiece Queen)), Just (f (ChessPiece King)), Just (f (ChessPiece Bishop)), Just (f (ChessPiece Knight)), Just (f (ChessPiece Rook))]
To make the difference between type and data constructors more obvious, here's a limited version that that uses different names for each:
data ChessRoyalty = King | Queen
data Piece = ChessPiece ChessRoyalty | OtherGamePiece
data ColoredPiece = White Piece | Black Piece

Related

How to write the instance for Show of a given datatype shorter?

I´m quite new to Haskell but I wonder how I can write following Code shorter:
data Suite = Club | Heart | Spade | Diamond
data Value = Two | Three | Four | Five | Six | Seven | Eight | Nine | Ten | Jack | Queen |
King | Ace
data Card = Card Suite Value
instance Show Suite where
show Club = "Club"
show Heart = "Heart"
show Spade = "Spade"
show Diamond = "Diamond"
instance Enum Suite where
enumFromTo Club Diamond = [Club, Heart, Spade, Diamond]
enumFromTo Heart Diamond = [Heart, Spade, Diamond]
enumFromTo Club Spade = [Club, Heart, Spade]
instance Show Value where
show Two = "Two"
show Three = "Three"
show Four = "Four"
show Five = "Five"
show Six = "Six"
show Seven = "Seven"
show Eight = "Eight"
show Nine = "Nine"
show Ten = "Ten"
show Jack = "Jack"
show Queen = "Queen"
show King = "King"
show Ace = "Ace"
I want to write the instance for Show Value way shorter. Is there a good way to do this or do I need to write all of it?
I also wonder how i could go from here if I want to define the same instances for Eq Card, Ord Card?
So far
instance Eq Card where
Card _ _ == _ = False
instance Ord Card where
Card Heart Three > Card Heart Two = True
worked, but to write every single possibility would be quite a lot of work.
Thanks for any answers!
Edit: I´m aware of the possiblity to append deriving (Show, etc..) but I don´t want to use it
You've rejected deriving these instances, which is the main way we avoid that much boilerplate. The most obvious remaining elementary way to shorten the Show Value is to use a case expression. This uses an extra line but shortens each case slightly:
instance Show Value where
show x = case x of
Two -> "Two"
Three -> "Three"
-- etc.
Expanding to non-elementary ways, you could
Use generics, either the somewhat more modern version in GHC.Generics or (probably easier in this case) the one in Data.Data. For these, you'll need deriving Generic or deriving Data, respectively, and then you can write (or dig up on Hackage) generic versions of the class methods you need. Neither of these approaches seems very appropriate for a Haskell beginner, but you can work up to them over a number of months.
Use Template Haskell. This is a very advanced language feature, and despite working with Haskell for many years, I have not really begun to grasp how to program with it. Good luck!
If you just want your show method call to print the name of the constructor (as it appears here), there's no need to manually instance them at all. You can automatically derive the Show instance thusly:
data Suit = Club | Heart | Spade | Diamond
deriving Show
data Value = Two | Three | Four | Five | Six | Seven
| Eight | Nine | Ten | Jack | Queen | King | Ace
deriving Show
In some cases, such as Instance Show Value, there is no good way to shorten it without deriving (not counting the ones in dfeuer's answer).
But in others there is! E.g.
for the Enum instances it's enough to define fromEnum and toEnum, all the rest have default definitions. You certainly don't need to list all possibilities in enumFromTo as your example code does.
After you define instance Enum Value, you can write comparison functions by converting to Int and comparing the results:
instance Eq Value where
x == y = fromEnum x == fromEnum y
instance Ord Value where
compare x y = compare (fromEnum x) (fromEnum y)
You can use instances for Value and Suit when writing definitions for Card, e.g.
instance Eq Card where
Card s1 v1 == Card s2 v2 = s1 == s2 && v1 == v2

Factoring out recursion in a complex AST

For a side project I am working on I currently have to deal with an abstract syntax tree and transform it according to rules (the specifics are unimportant).
The AST itself is nontrivial, meaning it has subexpressions which are restricted to some types only. (e.g. the operator A must take an argument which is of type B only, not any Expr. A drastically simplified reduced version of my datatype looks like this:
data Expr = List [Expr]
| Strange Str
| Literal Lit
data Str = A Expr
| B Expr
| C Lit
| D String
| E [Expr]
data Lit = Int Int
| String String
My goal is to factor out the explicit recursion and rely on recursion schemes instead, as demonstrated in these two excellent blog posts, which provide very powerful general-purpose tools to operate on my AST. Applying the necessary factoring, we end up with:
data ExprF a = List [a]
| Strange (StrF a)
| Literal (LitF a)
data StrF a = A a
| B a
| C (LitF a)
| D String
| E [a]
data LitF a = Int Int
| String String
If I didn't mess up, type Expr = Fix ExprF should now be isomorphic to the previously defined Expr.
However, writing cata for these cases becomes rather tedious, as I have to pattern match B a :: StrF a inside of an Str :: ExprF a for cata to be well-typed. For the entire original AST this is unfeasible.
I stumbled upon fixing GADTs, which seems to me like it is a solution to my problem, however the user-unfriendly interface of the duplicated higher-order type classes etc. is quite the unneccessary boilerplate.
So, to sum up my questions:
Is rewriting the AST as a GADT the correct way to go about this?
If yes, how could I transform the example into a well-working version? On a second note, is there better support for higher kinded Functors in GHC now?
If you've gone through the effort of to separate out the recursion in your data type, then you can just derive Functor and you're done. You don't need any fancy features to get the recursion scheme. (As a side note, there's no reason to parameterize the Lit data type.)
The fold is:
newtype Fix f = In { out :: f (Fix f) }
gfold :: (Functor f) => (f a -> a) -> Fix f -> a
gfold alg = alg . fmap (gfold alg) . out
To specify the algebra (the alg parameter), you need to do a case analysis against ExprF, but the alternative would be to have the fold have a dozen or more parameters: one for each data constructor. That wouldn't really save you much typing and would be much harder to read. If you want (and this may require rank-2 types in general), you can package all those parameters up into a record and then you could use record update to update "pre-made" records that provide "default" behavior in various circumstances. There's an old paper Dealing with Large Bananas that takes an approach like this. What I'm suggesting, to be clear, is just wrapping the gfold function above with a function that takes a record, and passes in an algebra that will do the case analysis and call the appropriate field of the record for each case.
Of course, you could use GHC Generics or the various "generic/polytypic" programming libraries like Scrap Your Boilerplate instead of this. You are basically recreating what they do.

Is there some way to reduce the pain of range tracking?

There's currently a pull request by Jonathan S. to replace the implementation of Data.IntMap with one explained in this README based on ideas from a blog post by Edward Kmett.
The basic concept Jonathan S. developed from is that an IntMap is a binary tree that looks like this (I've made some slight changes to his development for the sake of consistency):
data IntMap0 a = Empty | NonEmpty (IntMapNE0 a)
data IntMapNE0 a =
Tip !Int a
| Bin { lo :: !Int
, hi :: !Int
, left :: !(IntMapNE0 a)
, right :: !(IntMapNE0 a) }
In this representation, each node has a field indicating the least and greatest key contained in the IntMapNE0. Using just a little bit fiddling allows this to be used as a PATRICIA trie. Jonathan noted that this structure has almost twice as much range information as it needs. Following a left or right spine will produce all the same lo or hi bounds. So he cut those out by only including the bound not determined by the ancestors:
data IntMap1 a = Empty | NonEmpty { topLo :: !Int, child :: !(IntMapNE1 a) }
data IntMapNE1 a =
Tip a
| IntMapNE1 { bound :: !Int
, left :: !(IntMapNE1 a)
, right :: !(IntMapNE1 a)
Now each node has either a left bound or a right bound, but not both. A right child will have only a left bound, while a left child will have only a right bound.
Jonathan makes one further change, moving the values out of the leaves and into the internal nodes, which places them exactly where they are determined. He also uses phantom types to help track left and right. The final type (for now, anyway) is
data L
data R
newtype IntMap a = IntMap (IntMap_ L a) deriving (Eq)
data IntMap_ t a = NonEmpty !Int a !(Node t a) | Empty deriving (Eq)
data Node t a = Bin !Int a !(Node L a) !(Node R a) | Tip deriving (Eq, Show)
Certain aspects of this new implementation are quite attractive. Most importantly, many of the most-used operations are substantially faster. Less importantly, but very nicely, the bit fiddling involved is much easier to understand.
However, there is one serious pain point: passing the missing range information down through the tree. This isn't so bad for lookups, insertions, etc., but gets pretty seriously hairy in the union and intersection code. Is there some abstraction that would allow this to be done automatically?
A couple extremely vague thoughts:
Could the phantom types be used with a custom class to tie treatment directly to handedness?
The "missing piece" nature is somewhat reminiscent of some zippery situations. Might there be a way to use ideas from that realm?
I've started thinking about using an intermediate type of some sort to provide a symmetrical "view" of the structure, but I'm a bit stuck. I can fairly easily convert back and forth between the basic structure and the fancy one, but that conversion is recursive. I need a way to convert only partially, but I don't know nearly enough about fancily built types to get it done.
Is there some abstraction that would allow this to be done automatically?
You should be able to define a set of pattern synonyms that give you that. I’ll start from the second-to-last variant of your code, i.e.:
data IntMap1 a = Empty | NonEmpty { topLo :: !Int, child :: !(IntMapNE1 a) }
data IntMapNE1 a =
Tip a
| IntMapNE1 { bound :: !Int
, left :: !(IntMapNE1 a)
, right :: !(IntMapNE1 a)
We tuple such a value with the bound from the parent in an Either (indicating whether it is a low or a high bound).
viewLoHi (Left lo, IntMapNE1 hi left right)
= Just (lo, hi, (Left lo, left), (Right hi, right)
viewLoHi (Right hi, IntMapNE1 lo left right)
= Just (lo, hi, (Left lo, left), (Right hi, right)
viewLoHi _
= Nothing
pattern Bin' lo hi left right <- (viewLoHi -> Just (lo, hi, left, right))
The top-level data type is different, so it needs its own pattern synonym
viewLoHi' (NonEmpty lo child) = viewLoHi (Left lo, child)
viewLoHi' Empty = Nothing
pattern NonEmpty' lo hi left right <- (viewLoHi' -> Just (lo, hi, left, right)
Using only NonEmpty' and Bin' as you traverse the tree, the bookkeeping should now be completely hidden. (Code not tested, so there will be typos here)

haskell type,new type or data for only an upper case char

If i want to make a String but holds only an uppercase character. I know that String is a [Char]. I have tried something like type a = ['A'..'Z'] but it did not work any help?
What you're wanting is dependent types, which Haskell doesn't have. Dependent types are those that depend on values, so using dependent types you could encode at the type level a vector with length 5 as
only5 :: Vector 5 a -> Vector 10 a
only5 vec = concatenate vec vec
Again, Haskell does not have dependent types, but languages like Agda, Coq and Idris do support them. Instead, you could just use a "smart constructor"
module MyModule
( Upper -- export type only, not constructor
, mkUpper -- export the smart constructor
) where
import Data.Char (isUpper)
newtype Upper = Upper String deriving (Eq, Show, Read, Ord)
mkUpper :: String -> Maybe Upper
mkUpper s = if all isUpper s then Just (Upper s) else Nothing
Here the constructor Upper is not exported, just the type, and then users of this module have to use the mkUpper function that safely rejects non-uppercase strings.
For clarification, and to show how awesome dependent types can be, consider the mysterious concatenate function from above. If I were to define this with dependent types, it would actually look something like
concatenate :: Vector n a -> Vector m a -> Vector (n + m) a
concatenate v1 v2 = undefined
Wait, what's arithmetic doing in a type signature? It's actually performing type-system level computations on the values that this type is dependent on. This removes a lot of potential boilerplate in Haskell, and it makes guarantees at compilation time that, e.g., arrays can't have negative length.
Most desires for dependent types can be filled either using smart constructors (see bheklilr's answer), generating Haskell from an external tool (Coq, Isabelle, Inch, etc), or using an exact representation. You probably want the first solution.
To exactly represent just the capitals then you could write a data type that includes a constructor for each letter and conversion to/from strings:
data Capital = CA | CB | CC | CD | CE | CF | CG | CH | CI | CJ | CK | CL | CM | CN | CO | CP | CQ | CR | CS | CT | CU | CV | CW | CX | CY | CZ deriving (Eq, Ord, Enum)
toString :: [Capital] -> String
toString = map (toEnum . (+ (fromEnum 'A')) . fromEnum)
You can even go a step further and allow conversion from string literals, "Anything in quotes", to a type [Capitals] by using the OverloadedStrings extension. Just add to the top of your file {-# LANGUAGE OverloadedStrings, FlexibleInstances #-}, be sure to import Data.String and write the instance:
type Capitals = [Capital]
instance IsString Capitals where
fromString = map (toEnum . (subtract (fromEnum 'A')) . fromEnum) . filter (\x -> 'A' <= x && x <= 'Z')
After that, you can type capitals all you want!
*Main> toString ("jfoeaFJOEW" :: Capitals)
"FJOEW"
*Main>
bheklilr is correct but perhaps for your purposes the following could be OK:
import Data.Char(toUpper)
newtype UpperChar = UpperChar Char
deriving (Show)
upperchar :: Char -> UpperChar
upperchar = UpperChar. toUpper
You can alternatively make UpperChar an alias of Char (use type instead of newtype) which would allow you to forms lists of both Char and UpperChar. The problem with an alias, however, is that you could feed a Char into a function expecting an UpperChar...
One way to do something similar which will work well for the Latin script of your choice but not so well as a fully general solution is to use a custom type to represent upper case letters. Something like this should do the trick:
data UpperChar = A|B|C|D| (fill in the rest) | Y | Z deriving (Enum, Eq, Ord, Show)
newtype UpperString = UpperString [UpperChar]
instance Show UpperString
show (UpperString s) = map show s
The members of this type are not Haskell Strings, but you can convert between them as needed.

Subtypes for natural language types

I'm a linguist working on the formal syntax/semantics of Natural Languages. I've started
using Haskell quite recently and very soon I realized that I needed to add subtyping. For example given the types Human
and Animal,
I would like to have Human as a subtype of Animal. I found that this is possible using a coerce function where the instances are declared by the user, but I do not know how to define coerce in the instances I'm interested in. So basically I do not know what to add after 'coerce =' to make it work'. Here is the code up to that point:
{-# OPTIONS
-XMultiParamTypeClasses
-XFlexibleInstances
-XFunctionalDependencies
-XRankNTypes
-XTypeSynonymInstances
-XTypeOperators
#-}
module Model where
import Data.List
data Animal = A|B deriving (Eq,Show,Bounded,Enum)
data Man = C|D|E|K deriving (Eq,Show,Bounded,Enum)
class Subtype a b where
coerce :: a->b
instance Subtype Man Animal where
coerce=
animal:: [Animal]
animal = [minBound..maxBound]
man:: [Man]
man = [minBound..maxBound]
Thanks in advance
Just ignore the Subtype class for a second and examine the type of the coerce function you are writing. If the a is a Man and the b is an Animal, then the type of the coerce function you are writing should be:
coerce :: Man -> Animal
This means that all you have to do is write a sensible function that converts each one of your Man constructors (i.e. C | D | E | K) to a corresponding Animal constructor (i.e. A | B). That's what it means to subtype, where you define some function that maps the "sub" type onto the original type.
Of course, you can imagine that because you have four constructors for your Man type and only two constructors for your Animal type then you will end up with more than one Man constructor mapping to the same Animal constructor. There's nothing wrong with that and it just means that the coerce function is not reversible. I can't comment more on that without knowing exactly what those constructors were meant to represent.
The more general answer to your question is that there is no way to automatically know which constructors in Man should map to which constructors in Animal. That's why you have to write the coerce function to tell it what the relationship between men and animals is.
Note also that there is nothing special about the 'Subtype' class and 'coerce' function. You can just skip them and write an 'manToAnimal' function. After all there is no built-in language or compiler support for sub-typing and Subtype is just another class that some random guy came up with (and frankly, subtyping is not really idiomatic Haskell, but you didn't really ask about that). All that defining the class instance does is allow you to overload the function coerce to work on the Man type.
I hope that helps.
What level of abstraction are you working where you "need to add subtyping"?
Are you trying to create world model for your program encoded by Haskell types? (I can see this if your types are actually Animal, Dog, etc.)
Are you trying to create more general software, and you think subtypes would be a good design?
Or are you just learning haskell and playing around with things.
If (1), I think that will not work out for you so well. Haskell does not have very good reflective abilities -- i.e. ability to weave type logic into runtime logic. Your model would end up pretty deeply entangled with the implementation. I would suggest creaing a "world model" (set of) types, as opposed to a set of types corresponding to a specific world model. I.e., answer this question for Haskell: what is a world model?
If (2), think again :-). Subtyping is part of a design tradition in which Haskell does not participate. There are other ways to design your program, and they will end up playing nicer with the functional mindset then subtyping would have. It takes times to develop your functional design sense, so be patient with it. Just remember: keep it simple, stupid. Use data types and functions over them (but remember to use higher-order functions to generalize and share code). If you are reaching for advanced features (even typeclasses are fairly advanced in the sense I mean), you are probably doing it wrong.
If (3), see Doug's answer, and play with stuff. There are lots of ways to fake it, and they all kind of suck eventually.
I don't know much about Natural Languages so my suggestion may be missing the point, but this may be what you are looking for.
{-# OPTIONS
-XMultiParamTypeClasses
-XFlexibleContexts
#-}
module Main where
data Animal = Mammal | Reptile deriving (Eq, Show)
data Dog = Terrier | Hound deriving (Eq, Show)
data Snake = Cobra | Rattle deriving (Eq, Show)
class Subtype a b where
coerce :: a -> b
instance Subtype Animal Animal where
coerce = id
instance Subtype Dog Animal where
coerce _ = Mammal
instance Subtype Snake Animal where
coerce _ = Reptile
isWarmBlooded :: (Subtype a Animal) => a -> Bool
isWarmBlooded = (Mammal == ) . coerce
main = do
print $ isWarmBlooded Hound
print $ isWarmBlooded Cobra
print $ isWarmBlooded Mammal
Gives you:
True
False
True
Is that kind of what you are shooting for? Haskell doesn't have subtyping built-in, but this might do as a work-around. Admittedly, there are probably better ways to do this.
Note: This answer is not intended to point out the best, correct or idomatic way to solve the problem at hand. It is intended to answer the question which was "what to add after 'coerce=' to make it work."
You can't write the coerce function you're looking for — at least, not sensibly. There aren't any values in Animal that correspond with the values in Man, so you can't write a definition for coerce.
Haskell doesn't have subtyping as an explicit design decision, for various reasons (it allows type inference to work better, and allowing subtyping vastly complicates the language's type system). Instead, you should express relationships like this using aggregation:
data Animal = A | B | AnimalMan Man deriving (Eq, Show, Bounded, Enum)
data Man = C | D | E | K deriving (Eq, Show, Bounded, Enum)
AnimalMan now has the type Man -> Animal, exactly as you wanted coerce to have.
If I understood you correctly, it is quite possible. We will use type classes and generalized algebraic data types to implement this functionality.
If you want to be able to do something like this (where animals and humans can be fed but only humans can think):
animals :: [AnyAnimal]
animals = (replicate 5 . AnyAnimal $ SomeAnimal 10) ++ (replicate 5 . AnyAnimal $ SomeHuman 10 10)
humans :: [AnyHuman]
humans = replicate 5 . AnyHuman $ SomeHuman 10 10
animals' :: [AnyAnimal]
animals' = map coerce humans
animals'' :: [AnyAnimal]
animals'' = (map (\(AnyAnimal x) -> AnyAnimal $ feed 50 x) animals) ++
(map (\(AnyAnimal x) -> AnyAnimal $ feed 50 x) animals') ++
(map (\(AnyHuman x) -> AnyAnimal $ feed 50 x) humans)
humans' :: [AnyHuman]
humans' = (map (\(AnyHuman x) -> AnyHuman . think 100 $ feed 50 x) humans)
Then it's possible, for example:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
-- | The show is there only to make things easier
class (Show a) => IsAnimal a where
feed :: Int -> a -> a
-- other interface defining functions
class (IsAnimal a) => IsHuman a where
think :: Int -> a -> a
-- other interface defining functions
class Subtype a b where
coerce :: a -> b
data AnyAnimal where
AnyAnimal :: (IsAnimal a) => a -> AnyAnimal
instance Show AnyAnimal where
show (AnyAnimal x) = "AnyAnimal " ++ show x
data AnyHuman where
AnyHuman :: (IsHuman a) => a -> AnyHuman
instance Show AnyHuman where
show (AnyHuman x) = "AnyHuman " ++ show x
data SomeAnimal = SomeAnimal Int deriving Show
instance IsAnimal SomeAnimal where
feed = flip const
data SomeHuman = SomeHuman Int Int deriving Show
instance IsAnimal SomeHuman where
feed = flip const
instance IsHuman SomeHuman where
think = flip const
instance Subtype AnyHuman AnyAnimal where
coerce (AnyHuman x) = AnyAnimal x
animals :: [AnyAnimal]
animals = (replicate 5 . AnyAnimal $ SomeAnimal 10) ++ (replicate 5 . AnyAnimal $ SomeHuman 10 10)
humans :: [AnyHuman]
humans = replicate 5 . AnyHuman $ SomeHuman 10 10
animals' :: [AnyAnimal]
animals' = map coerce humans
Few comments:
You can make AnyAnimal and AnyHuman instances of their respective classes for convenience (atm. you have to unpack them first and pack them afterwards).
We could have single GADT AnyAnimal like this (both approaches have their use I would guess):
data AnyAnimal where
AnyAnimal :: (IsAnimal a) => a -> AnyAnimal
AnyHuman :: (IsHuman a) => a -> AnyAnimal
instance Show AnyHuman where
show (AnyHuman x) = "AnyHuman " ++ show x
show (AnyAnimal x) = "AnyAnimal " ++ show x
instance Subtype AnyAnimal AnyAnimal where
coerce (AnyHuman x) = AnyAnimal x
coerce (AnyAnimal x) = AnyAnimal x
It's rather advanced, but have a look at Edward Kmett's work on using the new Constraint kinds for this kind of functionality.

Resources