41

I want to build a list of different things which have one property in common, namely, they could be turned into string. The object-oriented approach is straightforward: define interface Showable and make classes of interest implement it. Second point can in principle be a problem when you can't alter the classes, but let's pretend this is not the case. Then you create a list of Showables and fill it with objects of these classes without any additional noise (e.g. upcasting is usually done implicitly). Proof of concept in Java is given here.

My question is what options for this do I have in Haskell? Below I discuss approaches that I've tried and which don't really satisfy me.

Approach 1: existensials. Works but ugly.

{-# LANGUAGE ExistentialQuantification #-}
data Showable = forall a. Show a => Sh a

aList :: [Showable]
aList = [Sh (1 :: Int), Sh "abc"]

The main drawback for me here is the necessity for Sh when filling the list. This closely resembles upcast operations which are implicitly done in OO-languages.

More generally, the dummy wrapper Showable for the thing which is already in the language — Show type class — adds extra noise in my code. No good.

Approach 2: impredicatives. Desired but does not work.

The most straightforward type for such a list for me and what I really desire would be:

{-# LANGUAGE ImpredicativeTypes #-}
aList :: [forall a. Show a => a]
aList = [(1 :: Int), "abc"]

Besides that (as I heard)ImpredicativeTypes is “fragile at best and broken at worst” it does not compile:

Couldn't match expected type ‘a’ with actual type ‘Int’
  ‘a’ is a rigid type variable bound by
      a type expected by the context: Show a => a

and the same error for "abc". (Note type signature for 1: without it I receive even more weird message: Could not deduce (Num a) arising from the literal ‘1’).

Approach 3: Rank-N types together with some sort of functional lists (difference lists?).

Instead of problematic ImpredicativeTypes one would probably prefer more stable and wide-accepted RankNTypes. This basically means: move desired forall a. Show a => a out of type constructor (i.e. []) to plain function types. Consequently we need some representation of lists as plain functions. As I barely heard there are such representations. The one I heard of is difference lists. But in Dlist package the main type is good old data so we return to impredicatives. I didn't investigate this line any further as I suspect that it could yield more verbose code than in approach 1. But if you think it won't, please give me an example.

Bottom line: how would you attack such a task in Haskell? Could you give more succinct solution than in OO-language (especially in place of filling a list — see comment for code in approach 1)? Can you comment on how relevant are the approaches listed above?

UPD (based on first comments): the question is of course simplified for the purpose of readability. The real problem is more about how to store things which share the same type class, i.e. can be processed later on in a number of ways (Show has only one method, but other classes can have more than one). This factors out solutions which suggest apply show method right when filling a list.

Artem Pelenitsyn
  • 2,508
  • 22
  • 38
  • 20
    There is a key difference between Java and Haskell that you are missing. In Java, the type information is _not lost_ when upcasting, so you can downcast again and do other useful non-`String`y things later (conditioned on choosing the right type to downcast to). In Haskell, once you've upcast, the type information is *lost* and you cannot downcast again. So you might as well just have a list of `String`s. See also [`Dynamic`](http://hackage.haskell.org/package/base-4.8.1.0/docs/Data-Dynamic.html), which offers a richer interface than "just `String`". – Daniel Wagner Nov 07 '15 at 19:25
  • @DanielWagner not really sure how downcasting is connected with the topic. I need only upcast. Yes I can turn this into list of `String`s as mentioned in the answer by @ErikR but the question more about readability: repetetive `show`s doesn't look good for me. – Artem Pelenitsyn Nov 07 '15 at 19:30
  • 1
    It is not always easy to tell whether downcasting is connected to the topic at hand or not -- people often include it in their assumptions so hard they forget to mention it. (This is not the first time this topic has come up, neither here nor on IRC. ;-) As for "it doesn't look good to me", well, there's no accounting for taste. If you can give an objective, technical complaint we may be able to talk about the extent to which it can be addressed. – Daniel Wagner Nov 07 '15 at 19:38
  • 31
    I don't like the title of this question very much. It purports a conflict between languages/paradigms, possibly calling people on one side to fight in a language war. – chi Nov 07 '15 at 19:46
  • 9
    This is a known antipattern, also discussed in [Luke Palmer's blog](https://lukepalmer.wordpress.com/2010/01/24/haskell-antipattern-existential-typeclass/). While I do not completely agree with the whole blog post, I believe the basic point he makes is solid. – chi Nov 07 '15 at 19:49
  • @ArtemPelenitsyn You say that the real problem is more about how to store things which share the same type class which can have more than one method. Give us an example. We can't give you an accurate answer until you give us an accurate question. – Aadit M Shah Nov 07 '15 at 20:42
  • 11
    From the Hot Network Questions-optimized title, I arrived ready to vote to close as opinion-based. I was pleasantly surprised by the question's quality, but once your 15 minutes of HNQ are over, try changing the title to something less likely to attract bad answers. – Jeffrey Bosboom Nov 07 '15 at 21:24
  • 1
    Can this generally work? E.g. for the `Eq` instance, wouldn't you have to enable comparison of different types - which should be type-wise impossible? – ondra Nov 07 '15 at 21:51
  • 2
    For what it's worth, your second attempt (with impredicative types) is not the same as the first and is definitely not what you want. A `[forall a. Show a => a]` is a list of inhabitants of `forall a. Show a => a`. There is only one inhabitant of this type -- bottom. There is no other possible value that can become *any* `Show` that the caller asks for. No Int can inhabit that type, no String...nothing. It's literally the opposite of what you originally wanted. You probably wanted `[exists a. Show a => a]`, or, skolemized, `[(forall a. Show a => a -> r) -> r]`. – Justin L. Aug 18 '17 at 21:23

8 Answers8

38

Since evaluation is lazy in Haskell, how about just creating a list of the actual strings?

showables = [ show 1, show "blah", show 3.14 ]
ErikR
  • 51,541
  • 9
  • 73
  • 124
  • This is an option, thank's! Still this resembles the problem mentioned in first approach: weird repetition which looks like (up)casting. Examples in my post are hugely simplified: in real application I get showable things from different algorithms and I prefer not to mix them with show. – Artem Pelenitsyn Nov 07 '15 at 19:26
  • 1
    You'd need to gather them into list anyway and then you can `map show`. – arrowd Nov 07 '15 at 19:37
  • 12
    @arrowd That's not well-typed: you can't gather them into a list before applying `show`, which is essentially what the body of the question as asked is complaining about. – Daniel Wagner Nov 07 '15 at 19:38
  • 1
    I see I chose bad example for the post. Consider the case of type class which (unlike `Show`) have more than one method. This solution besides its unpleasant form (hand-written map is not cool) will not work for this. – Artem Pelenitsyn Nov 07 '15 at 19:45
  • 6
    How about coming up with a concrete example in Java that you want translated into Haskell. That would help direct this discussion. – ErikR Nov 07 '15 at 19:56
  • 3
    @ArtemPelenitsyn When there are several methods, one may represent those methods in a custom data type with one field per method. – Daniel Wagner Nov 07 '15 at 20:29
  • 1
    @arrowd you can handle multiple methods by wrapping each value in a record containing a field per method. This way, you just need one wrapper by type `a -> WrappedRecord`. – mb14 Nov 07 '15 at 20:32
  • Why didn't anyone think of [variadic argument functions](http://stackoverflow.com/a/7828634/783743) for this problem? It's the perfect solution. See my answer for more details: http://stackoverflow.com/a/33587266/783743 – Aadit M Shah Nov 07 '15 at 20:32
  • @DanielWagner one thing to add to that (you probably already know this but for someone less familiar with Haskell that is reading) is that doing so does NOT cause any performance decrease even if you choose to only use some of the methods, or some on certain parts of the list and other on other parts of the list, due to really powerful lazy evaluation. – semicolon Mar 20 '16 at 02:59
19

The HList-style solutions would work, but it is possible to reduce the complexity if you only need to work with lists of constrained existentials and you don't need the other HList machinery.

Here's how I handle this in my existentialist package:

{-# LANGUAGE ConstraintKinds, ExistentialQuantification, RankNTypes #-}

data ConstrList c = forall a. c a => a :> ConstrList c
                  | Nil
infixr :>

constrMap :: (forall a. c a => a -> b) -> ConstrList c -> [b]
constrMap f (x :> xs) = f x : constrMap f xs
constrMap f Nil       = []

This can then be used like this:

example :: [String]
example
  = constrMap show
              (( 'a'
              :> True
              :> ()
              :> Nil) :: ConstrList Show)

It could be useful if you have a large list or possibly if you have to do lots of manipulations to a list of constrained existentials.

Using this approach, you also don't need to encode the length of the list in the type (or the original types of the elements). This could be a good thing or a bad thing depending on the situation. If you want to preserve the all of original type information, an HList is probably the way to go.

Also, if (as is the case of Show) there is only one class method, the approach I would recommend would be applying that method to each item in the list directly as in ErikR's answer or the first technique in phadej's answer.

It sounds like the actual problem is more complex than just a list of Show-able values, so it is hard to give a definite recommendation of which of these specifically is the most appropriate without more concrete information.

One of these methods would probably work out well though (unless the architecture of the code itself could be simplified so that it doesn't run into the problem in the first place).

Generalizing to existentials contained in higher-kinded types

This can be generalized to higher kinds like this:

data AnyList c f = forall a. c a => f a :| (AnyList c f)
                 | Nil
infixr :|

anyMap :: (forall a. c a => f a -> b) -> AnyList c f -> [b]
anyMap g (x :| xs) = g x : anyMap g xs
anyMap g Nil       = []

Using this, we can (for example) create a list of functions that have Show-able result types.

example2 :: Int -> [String]
example2 x = anyMap (\m -> show (m x))
                    (( f
                    :| g
                    :| h
                    :| Nil) :: AnyList Show ((->) Int))
  where
    f :: Int -> String
    f = show

    g :: Int -> Bool
    g = (< 3)

    h :: Int -> ()
    h _ = ()

We can see that this is a true generalization by defining:

type ConstrList c = AnyList c Identity

(>:) :: forall c a. c a => a -> AnyList c Identity -> AnyList c Identity
x >: xs  = Identity x :| xs
infixr >:

constrMap :: (forall a. c a => a -> b) -> AnyList c Identity -> [b]
constrMap f (Identity x :| xs) = f x : constrMap f xs
constrMap f Nil                = []

This allows the original example from the first part of this to work using this new, more general, formulation with no changes to the existing example code except changing :> to >: (even this small change might be able to be avoided with pattern synonyms. I'm not totally sure though since I haven't tried and sometimes pattern synonyms interact with existential quantification in ways that I don't fully understand).

David Young
  • 10,713
  • 2
  • 33
  • 47
  • 1
    Nice! I like your answer best of all, but would you explain, how to generalize this solution to list of functions like [Int -> Showable]? – Artem Pelenitsyn Nov 08 '15 at 17:07
  • 1
    @ArtemPelenitsyn I added a way to do that to my answer – David Young Nov 09 '15 at 01:49
  • 1
    @ArtemPelenitsyn I have to say, I'm a bit curious what your particular application of this is. Even though I've spent some time getting this kinda stuff to work in the past, I've never really used it for anything and I've always wondered if there are practical applications for it. – David Young Nov 09 '15 at 01:58
  • initial purpose was to develop a small demonstration framework to show students how various auto-deriving mechanisms work in Haskell. Take e.g. `DerivingFoldable` and `DerivingFunctor`. I want to make a list of simple algorithms that we get for free from these, like `sum` and `fmap`. But the problem is that the algorithms return values of different types. For the purpose of demonstration I need those values to be showable. If I add GUI to this app, I probably would like them to share some other GUI-awared class. – Artem Pelenitsyn Nov 09 '15 at 08:18
11

If you really, really want, you can use a heterogeneous list. This approach really isn't useful for Show, because it has a single method and all you can do is apply it, but if your class has multiple methods this could be useful.

{-# LANGUAGE PolyKinds, KindSignatures, GADTs, TypeFamilies
   , TypeOperators, DataKinds, ConstraintKinds, RankNTypes, PatternSynonyms  #-} 

import Data.List (intercalate)
import GHC.Prim (Constraint)

infixr 5 :&
data HList xs where 
  None :: HList '[] 
  (:&) :: a -> HList bs -> HList (a ': bs) 

-- | Constraint All c xs holds if c holds for all x in xs
type family All (c :: k -> Constraint) xs :: Constraint where 
  All c '[] = () 
  All c (x ': xs) = (c x, All c xs) 

-- | The list whose element types are unknown, but known to satisfy
--   a class predicate. 
data CList c where CL :: All c xs => HList xs -> CList c  

cons :: c a => a -> CList c -> CList c
cons a (CL xs) = CL (a :& xs) 

empty :: CList c 
empty = CL None 

uncons :: (forall a . c a => a -> CList c -> r) -> r -> CList c -> r 
uncons _ n (CL None) = n 
uncons c n (CL (x :& xs)) = c x (CL xs) 

foldrC :: (forall a . c a => a -> r -> r) -> r -> CList c -> r 
foldrC f z = go where go = uncons (\x -> f x . go) z 

showAll :: CList Show -> String 
showAll l = "[" ++ intercalate "," (foldrC (\x xs -> show x : xs) [] l) ++ "]" 

test = putStrLn $ showAll $ CL $ 
  1 :& 
  'a' :& 
  "foo" :& 
  [2.3, 2.5 .. 3] :& 
  None 
user2407038
  • 14,400
  • 3
  • 29
  • 42
9

You can create your own operator to reduce syntax noise:

infixr 5 <:

(<:) :: Show a => a -> [String] -> [String]
x <: l = show x : l

So you can do:

λ > (1 :: Int) <: True <: "abs" <: []
["1","True","\"abs\""]

This is not [1 :: Int, True, "abs"] but not much longer.

Unfortunately you cannot rebind [...] syntax with RebindableSyntax.


Another approach is to use HList and preserve all type information, i.e. no downcasts, no upcasts:

{-# LANGUAGE ConstraintKinds       #-}
{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE GADTs                 #-}
{-# LANGUAGE PolyKinds             #-}
{-# LANGUAGE TypeFamilies          #-}
{-# LANGUAGE TypeOperators         #-}
{-# LANGUAGE UndecidableInstances  #-}

import GHC.Exts (Constraint)

infixr 5 :::

type family All (c :: k -> Constraint) (xs :: [k]) :: Constraint where
  All c '[]       = ()
  All c (x ': xs) = (c x, All c xs)

data HList as where
  HNil :: HList '[]
  (:::) :: a -> HList as -> HList (a ': as)

instance All Show as => Show (HList as) where
  showsPrec d HNil       = showString "HNil"
  showsPrec d (x ::: xs) = showParen (d > 5) (showsPrec 5 x)
                         . showString " ::: "
                         . showParen (d > 5) (showsPrec 5 xs)

And after all that:

λ *Main > (1 :: Int) ::: True ::: "foo" ::: HNil
1 ::: True ::: "foo" ::: HNil

λ *Main > :t (1 :: Int) ::: True ::: "foo" ::: HNil
(1 :: Int) ::: True ::: "foo" ::: HNil
  :: HList '[Int, Bool, [Char]]

There are various ways to encode heterogenous list, in HList is one, there is also generics-sop with NP I xs. It depends on what you are trying to achieve in the larger context, if this is this preserve-all-the-types approach is what you need.

phadej
  • 11,947
  • 41
  • 78
8

I would do something like this:

newtype Strings = Strings { getStrings :: [String] }

newtype DiffList a = DiffList { getDiffList :: [a] -> [a] }

instance Monoid (DiffList a) where
    mempty                          = DiffList id
    DiffList f `mappend` DiffList g = DiffList (f . g)

class ShowList a where
    showList' :: DiffList String -> a

instance ShowList Strings where
    showList' (DiffList xs) = Strings (xs [])

instance (Show a, ShowList b) => ShowList (a -> b) where
    showList' xs x = showList' $ xs `mappend` DiffList (show x :)

showList = showList' mempty

Now, you can create a ShowList as follows:

myShowList = showList 1 "blah" 3.14

You can get back a list of strings using getStrings as follows:

myStrings = getStrings myShowList

Here's what's happening:

  1. A value of the type ShowList a => a could be:

    1. Either a list of strings wrapped in a Strings newtype wrapper.
    2. Or a function from an instance of Show to an instance of ShowList.
  2. This means that the function showList is a variadic argument function which takes an arbitrary number of printable values and eventually returns a list of strings wrapped in a Strings newtype wrapper.

  3. You can eventually call getStrings on a value of the type ShowList a => a to get the final result. In addition, you don't need to do any explicit type coercion yourself.

Advantages:

  1. You can add new elements to your list whenever you want.
  2. The syntax is succinct. You don't have to manually add show in front of every element.
  3. It doesn't make use of any language extensions. Hence, it works in Haskell 98 too.
  4. You get the best of both worlds, type safety and a great syntax.
  5. Using difference lists, you can construct the result in linear time.

For more information on functions with variadic arguments, read the answer to the following question:

How does Haskell printf work?

Community
  • 1
  • 1
Aadit M Shah
  • 72,912
  • 30
  • 168
  • 299
6

My answer is fundamentally the same as ErikR's: the type that best embodies your requirements is [String]. But I'll go a bit more into the logic that I believe justifies this answer. The key is in this quote from the question:

[...] things which have one property in common, namely, they could be turned into string.

Let's call this type Stringable. But now the key observation is this:

That is, if your statement above is the whole specification of the Stringable type, then there is a pair functions with these signatures:

toString :: Stringable -> String
toStringable :: String -> Stringable

...such that the two functions are inverses. When two types are isomorphic, any program that uses either of the types can be rewritten in terms of the other without any change to its semantics. So Stringable doesn't let you do anything that String doesn't let you do already!

In more concrete terms, the point is that this refactoring is guaranteed to work no matter what:

  1. At every point in your program where you turn an object into a Stringable and stick that into a [Stringable], turn the object into a String and stick that into a [String].
  2. At every point in your program that you consume a Stringable by applying toString to it, you can now eliminate the call to toString.

Note that this argument generalizes to types more complex than Stringable, with many "methods". So for example, the type of "things that you can turn into either a String or an Int" is isomorphic to (String, Int). The type of "things that you can either turn into a String or combine them with a Foo to produce a Bar" is isomorphic to (String, Foo -> Bar). And so on. Basically, this logic leads to the "record of methods" encoding that other answers have brought up.

I think the lesson to draw from this is the following: you need a specification richer than just "can be turned into a string" in order to justify using any of the mechanisms you brought up. So for example, if we add the requirement that Stringable values can be downcast to the original type, an existential type now perhaps becomes justifiable:

{-# LANGUAGE GADTs #-}

import Data.Typeable

data Showable = Showable
    Showable :: (Show a, Typeable a) => a -> Stringable

downcast :: Typeable a => Showable -> Maybe a
downcast (Showable a) = cast a

This Showable type is not isomorphic to String, because the Typeable constraint allows us to implement the downcast function that allows us to distinguish between different Showables that produce the same string. A richer version of this idea can be seen in this "shape example" Gist.

Luis Casillas
  • 29,802
  • 7
  • 49
  • 102
3

You can store partially applied functions in the list.

Suppose we are building a ray-tracer with different shape that you can intersect.

data Sphere = ...
data Triangle = ...

data Ray = ...
data IntersectionResult = ...

class Intersect t where
      intersect :: t -> Ray -> Maybe IntersectionResult

instance Intersect Sphere where ...
instance Intersect Triangle where ...

Now, we can partially apply the intersect to get a list of Ray -> Maybe IntersectionResult such as:

myList :: [(Ray -> Maybe IntersectionResult)]
myList = [intersect sphere, intersect triangle, ...]

Now, if you want to get all the intersections, you can write:

map ($ ray) myList -- or map (\f -> f ray) myList

This can be extended a bit to handle an interface with multiples functions, for example, if you want to be able to get something of a shape :

class ShapeWithSomething t where
        getSomething :: t -> OtherParam -> Float

data ShapeIntersectAndSomething = ShapeIntersectAndSomething {
          intersect :: Ray -> Maybe IntersectionResult,
          getSomething :: OtherParam -> Float}

Something I don't know is the overhead of this approach. We need to store the pointer to the function and the pointer to the shape and this for each function of the interface, which is a lot compared to the shared vtable usually used in OO language. I don't have any idea if GHC is able to optimize this.

Guillaum
  • 170
  • 6
  • 1
    This approach is still convoluted for list creation. From my point of view it is only a problem with toy examples, where your list is short and hand written, but I don't think it is a problem in production code where you list comes from different function call. – Guillaum Nov 08 '15 at 18:37
3

The core of the problem is : you want to dispatch (read select which function to call) at runtime, depending on what the "type" of the object is. In Haskell this can be achieved by wrapping the data into a sum data type (which is called here ShowableInterface):

data ShowableInterface = ShowInt Int | ShowApple Apple | ShowBusiness Business

instance Show ShowableInterface where
   show (ShowInt i)      = show i
   show (ShowApple a)    = show a
   show (ShowBusiness b) = show b  

list=[ShowInt 2, ShowApple CrunchyGold, ShowBusiness MoulinRouge]

show list

would correspond to something like this in Java :

class Int implements ShowableInterface
{
   public show {return Integer.asString(i)};
}
class Apple implements ShowableInterface
{
   public show {return this.name};
}
class ShowBusiness implements ShowableInterface
{
   public show {return this.fancyName};
}

List list = new ArrayList (new Apple("CrunchyGold"), 
                           new ShowBusiness("MoulingRouge"), new Integer(2));

so in Haskell you need to explicitly wrap stuff into the ShowableInterface, in Java this wrapping is done implicitly on object creation.

credit goes to #haskell IRC for explaining this to me a year ago, or so.

jhegedus
  • 20,244
  • 16
  • 99
  • 167