List of showables: OOP beats Haskell?

后端 未结 8 1243
无人及你
无人及你 2020-12-24 06:46

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: defi

相关标签:
8条回答
  • 2020-12-24 07:08

    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 
    
    0 讨论(0)
  • 2020-12-24 07:13

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

    showables = [ show 1, show "blah", show 3.14 ]
    
    0 讨论(0)
  • 2020-12-24 07:13

    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.

    0 讨论(0)
  • 2020-12-24 07:15

    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).

    0 讨论(0)
  • 2020-12-24 07:16

    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?

    0 讨论(0)
  • 2020-12-24 07:20

    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.

    0 讨论(0)
提交回复
热议问题