Home > Back-end >  Haskell - types and if statements
Haskell - types and if statements

Time:03-06

Is there a good way to use type information to choose to do different things?

For example, this isn't valid Haskell, but I don't see why it couldn't be:

tostring :: (Show b) => b -> String
tostring x = f x where f = if b == String then tail . init . show else show

The important part is not getting the correct string out, but using the type of b as a way to switch between functionality/functions.

CodePudding user response:

I will answer the question as it is. Haskell erases all type information during compile time, mostly for efficiency reasons. By default, when a polymorphic function is called, e.g. f :: a->a, no type information is available, and f has no way to know what a actually is -- in this case, f can only be the identity function, fail to terminate, or raise an error.

For the rare cases where type information is needed, there is Typeable. A polymorphic function having type f :: Typeable a => ... is passed a run-time description of the type a, allowing it to test it. Essentially, the Typeable a constraint forces Haskell to keep the runtime information until run time. Note that such type information must be known at the call site -- either because f is called with a completely known type, or because f is called with a partially known type (say f x with x :: Maybe b) but there are suitable Typeable constraints in scope (Typeable b, in the previous example).

Anyway, here's an example:

{-# LANGUAGE TypeApplications, ScopedTypeVariables, GADTs #-}

import Data.Typeable

tostring :: forall b. (Show b, Typeable b) => b -> String
tostring x = case eqT @b @String of  -- if b==String
   Just Refl -> x                    -- then
   Nothing   -> show x               -- else

Note how we were able to return x in the "then" branch, since there it is known to be a String.

CodePudding user response:

@chi's answer already demonstrates how to use Typeable to do run-time type checking, but I'd like to point out that to me, this looks like exactly the thing typeclasses are meant for. For your example, the only problem is that you don't like the Show implementation for String: In that case, just create your own typeclass!

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}

-- The class
class MyShow a where
    myShow :: a -> String

-- The instance for String
-- (The `OVERLAPPING` pragma is required, because
-- otherwise GHC won't know which instance to choose for String)
instance {-# OVERLAPPING #-} MyShow [Char] where
    myShow = tail . init . show

-- For everything that is not a String, just copy the Show instance
instance Show a => MyShow a where
    myShow = show

EDIT: As pointed out by leftaroundabout, overlapping instances are complicated and can lead to some unexpected behavior. Look at the example at the bottom of the documentation.

  • Related