Home > Enterprise >  Handle mutliple different data types in same function
Handle mutliple different data types in same function

Time:09-17

In haskell, is it possible to create a function capable of handling multiple different datatypes for input and output?

For example, lets assume a function capable of doing pattern matching on [Char] and Int returning both datatypes respectively.

fun 1 = 2
fun "textIn" = "textOut"

Is this possible?

CodePudding user response:

As Willem Van Onsem points out, you can do something with a typeclass:

class Fun a where
  fun :: a -> a

instance Fun Integer where
  fun 1 = 2

instance Fun String where
  fun "textIn" = "textOut"

Whether this is sensible depends on the situation. Designing good classes is difficult, and I strongly recommend that Haskell beginners steer entirely clear of it. Start by learning to design your own functions and types, and to declare instances of standard/library classes.


freestyle points out that you can do something with algebraic data types (ADTs), and I think that's a much better place to start.

data Funny
  = FunnyInteger Integer
  | FunnyString String
  deriving Show -- so you can print these in GHCi

fun :: Funny -> Funny
fun (FunnyInteger 1) = FunnyInteger 2
fun (FunnyString "textIn") = FunnyString "textOut"

freestyle also mentions generalized algebraic data types (GADTs). These are definitely not for beginners, but as a hint toward the future...

data FooTy a where
  FooInteger :: FooTy Integer
  FooString :: FooTy String

foo :: FooTy a -> a -> a
foo FooInteger 1 = 2
foo FooString "textIn" = "textOut"

CodePudding user response:

By class Typeable:

{-# LANGUAGE ScopedTypeVariables #-}

import Control.Monad
import Data.Typeable
import Data.Foldable

fun :: Typeable a => a -> Maybe a
fun x = asum $ map ($x)
    [ appT $ \(x::Int) -> 2 <$ guard (x == 1)
    , appT $ \(x::String) -> "textOut" <$ guard (x == "textIn")
    ]

appT :: (Typeable a, Typeable b) => (b -> Maybe b) -> a -> Maybe a
appT f x = cast =<< f =<< cast x

main :: IO ()
main = do
    print $ fun (1 :: Int)
    print $ fun "textIn"
    print $ fun [1 :: Int, 2]

Output:

Just 2
Just "textOut"
Nothing

appT is helper function (maybe it's in some package). You can also see: Dynamic, syb.

But this is not Haskell idiomatic way usually.

  • Related