Implementation of "show" for function - haskell

I would like to implement the show method for (binary) functions and make it able to distingish endofunctions (a -> a).
Something like the pseudo-haskell code:
instance Show (a->b) where
show fun = "<<Endofunction>>" if a==b
show fun = "<<Function>>" if a\=b
How can I distinguish the two cases?

You need to enable some extensions:
{-# LANGUAGE OverlappingInstances, FlexibleInstances #-}
module FunShow where
instance Show ((->) a a) where
show _ = "<<Endofunction>>"
instance Show ((->) a b) where
show _ = "<<Function>>"
You need OverlappingInstances since the instance a -> b also matches endofunctions, so there's overlap, and you need FlexibleInstances because the language standard mandates that the type variables in instance declarations are distinct.
*FunShow> show not
"<<Endofunction>>"
*FunShow> show fst
"<<Function>>"
*FunShow> show id
"<<Endofunction>>"

Related

How to 'show' unshowable types?

I am using data-reify and graphviz to transform an eDSL into a nice graphical representation, for introspection purposes.
As simple, contrived example, consider:
{-# LANGUAGE GADTs #-}
data Expr a where
Constant :: a -> Expr a
Map :: (other -> a) -> Expr a -> Expr a
Apply :: Expr (other -> a) -> Expr a -> Expr a
instance Functor Expr where
fmap fun val = Map fun val
instance Applicative Expr where
fun_expr <*> data_expr = Apply fun_expr data_expr
pure val = Constant val
-- And then some functions to optimize an Expr AST, evaluate Exprs, etc.
To make introspection nicer, I would like to print the values which are stored inside certain AST nodes of the DSL datatype.
However, in general any a might be stored in Constant, even those that do not implement Show. This is not necessarily a problem since we can constrain the instance of Expr like so:
instance Show a => Show (Expr a) where
...
This is not what I want however: I would still like to be able to print Expr even if a is not Show-able, by printing some placeholder value (such as just its type and a message that it is unprintable) instead.
So we want to do one thing if we have an a implementing Show, and another if a particular a does not.
Furthermore, the DSL also has the constructors Map and Apply which are even more problematic. The constructor is existential in other, and thus we cannot assume anything about other, a or (other -> a). Adding constraints to the type of other to the Map resp. Apply constructors would break the implementation of Functor resp. Applicative which forwards to them.
But here also I'd like to print for the functions:
a unique reference. This is always possible (even though it is not pretty as it requires unsafePerformIO) using System.Mem.StableName.
Its type, if possible (one technique is to use show (typeOf fun), but it requires that fun is Typeable).
Again we reach the issue where we want to do one thing if we have an f implementing Typeable and another if f does not.
How to do this?
Extra disclaimer: The goal here is not to create 'correct' Show instances for types that do not support it. There is no aspiration to be able to Read them later, or that print a != print b implies a != b.
The goal is to print any datastructure in a 'nice for human introspection' way.
The part I am stuck at, is that I want to use one implementation if extra constraints are holding for a resp. (other -> a), but a 'default' one if these do not exist.
Maybe type classes with FlexibleInstances, or maybe type families are needed here? I have not been able to figure it out (and maybe I am on the wrong track all together).
Not all problems have solutions. Not all constraint systems have a satisfying assignment.
So... relax the constraints. Store the data you need to make a sensible introspective function in your data structure, and use functions with type signatures like show, fmap, pure, and (<*>), but not exactly equal to them. If you need IO, use IO in your type signature. In short: free yourself from the expectation that your exceptional needs fit into the standard library.
To deal with things where you may either have an instance or not, store data saying whether you have an instance or not:
data InstanceOrNot c where
Instance :: c => InstanceOrNot c
Not :: InstanceOrNot c
(Perhaps a Constraint-kinded Either-alike, rather than Maybe-alike, would be more appropriate. I suspect as you start coding this you will discover what's needed.) Demand that clients that call notFmap and friends supply these as appropriate.
In the comments, I propose parameterizing your type by the constraints you demand, and giving a Functor instance for the no-constraints version. Here's a short example showing how that might look:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
import Data.Kind
type family All cs a :: Constraint where
All '[] a = ()
All (c:cs) a = (c a, All cs a)
data Lol cs a where
Leaf :: a -> Lol cs a
Fmap :: All cs b => (a -> b) -> Lol cs a -> Lol cs b
instance Functor (Lol '[]) where
fmap f (Leaf a) = Leaf (f a)
fmap f (Fmap g garg) = Fmap (f . g) garg
Great timing! Well-typed recently released a library which allows you to recover runtime information. They specifically have an example of showing arbitrary values. It's on github at https://github.com/well-typed/recover-rtti.
It turns out that this is a problem which has been recognized by multiple people in the past, known as the 'Constrained Monad Problem'. There is an elegant solution, explained in detail in the paper The Constrained-Monad Problem by Neil Sculthorpe and Jan Bracker and George Giorgidze and Andy Gill.
A brief summary of the technique: Monads (and other typeclasses) have a 'normal form'. We can 'lift' primitives (which are constrained any way we wish) into this 'normal form' construction, itself an existential datatype, and then use any of the operations available for the typeclass we have lifted into. These operations themselves are not constrained, and thus we can use all of Haskell's normal typeclass functions.
Finally, to turn this back into the concrete type (which again has all the constraints we are interested in) we 'lower' it, which is an operation that takes for each of the typeclass' operations a function which it will apply at the appropriate time.
This way, constraints from the outside (which are part of the functions supplied to the lowering) and constraints from the inside (which are part of the primitives we lifted) are able to be matched, and finally we end up with one big happy constrained datatype for which we have been able to use any of the normal Functor/Monoid/Monad/etc. operations.
Interestingly, while the intermediate operations are not constrained, to my knowledge it is impossible to write something which 'breaks' them as this would break the categorical laws that the typeclass under consideration should adhere to.
This is available in the constrained-normal Hackage package to use in your own code.
The example I struggled with, could be implemented as follows:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE UndecidableInstances #-}
module Example where
import Data.Dynamic
import Data.Kind
import Data.Typeable
import Control.Monad.ConstrainedNormal
-- | Required to have a simple constraint which we can use as argument to `Expr` / `Expr'`.
-- | This is definitely the part of the example with the roughest edges: I have yet to figure out
-- | how to make Haskell happy with constraints
class (Show a, Typeable a) => Introspectable a where {}
instance (Show a, Typeable a) => Introspectable a where {}
data Expr' (c :: * -> Constraint) a where
C :: a -> Expr' c a
-- M :: (a -> b) -> Expr' a -> Expr' b --^ NOTE: This one is actually never used as ConstrainedNormal will use the 'free' implementation based on A + C.
A :: c a => Expr' c (a -> b) -> Expr' c a -> Expr' c b
instance Introspectable a => Show (Expr' Introspectable a) where
show e = case e of
C x -> "(C " ++ show x ++ ")"
-- M f x = "(M " ++ show val ++ ")"
A fx x -> "(A " ++ show (typeOf fx) ++ " " ++ show x ++ ")"
-- | In user-facing code you'd not want to expose the guts of this construction
-- So let's introduce a 'wrapper type' which is what a user would normally interact with.
type Expr c a = NAF c (Expr' c) a
liftExpr :: c a => Expr' c a -> Expr c a
liftExpr expr = liftNAF expr
lowerExpr :: c a => Expr c a -> Expr' c a
lowerExpr lifted_expr = lowerNAF C A lifted_expr
constant :: Introspectable a => a -> Expr c a
constant val = pure val -- liftExpr (C val)
You could now for instance write
ghci> val = constant 10 :: Expr Introspectable Int
(C 10)
ghci> (+2) <$> val
(C 12)
ghci> (+) <$> constant 10 <*> constant 32 :: Expr Introspectable Int
And by using Data.Constraint.Trivial (part of the trivial-constrained library, although it is also possible to write your own 'empty constrained') one could instead write e.g.
ghci> val = constant 10 :: Expr Unconstrained Int
which will work just as before, but now val cannot be printed.
The one thing I have not yet figured out, is how to properly work with subsets of constraints (i.e. if I have a function that only requires Show, make it work with something that is Introspectable). Currently everything has to work with the 'big' set of constraints.
Another minor drawback is of course that you'll have to annotate the constraint type (e.g. if you do not want constraints, write Unconstrained manually), as GHC will otherwise complain that c0 is not known.
We've reached the goal of having a type which can be optionally be constrained to be printable, with all machinery that does not need printing to work also on all instances of the family of types including those that are not printable, and the types can be used as Monoids, Functors, Applicatives, etc just as you like.
I think it is a beautiful approach, and want to commend Neil Sculthorpe et al. for their work on the paper and the constrained-normal library that makes this possible. It's very cool!

Get rid of show String in instance Show for polymorphic type

I have a type kinda data T a = T a
I want to declare Show instance for this type, something like
instance Show a => Show (T a) where
show (T smth) = ... ++ show smth
But I don't want to call show smth if a is String, because I don't need additional quotes
Is there any solution how to declare such an instance?
Thanks in advance
If you want to declare an instance of Show for T String you can use FlexibleInstances
{-# LANGUAGE FlexibleInstances #-}
data T a = T a
instance Show (T String) where
show (T smth) = smth
You would then need to provide explicit instances for other as that you wish to support.
If you want to retain your catch-all instance shown in your question too, you would then be into using OVERLAPS/OVERLAPPABLE
{-# LANGUAGE FlexibleInstances #-}
data T a = T a
instance {-# OVERLAPPABLE #-} Show a => Show (T a) where
show (T smth) = show smth
instance {-# OVERLAPPING #-} Show (T String) where
show (T smth) = smth

Is there a way to show "showable" stuff [duplicate]

Suppose I have a simple data type in Haskell for storing a value:
data V a = V a
I want to make V an instance of Show, regardless of a's type. If a is an instance of Show, then show (V a) should return show a otherwise an error message should be returned. Or in Pseudo-Haskell:
instance Show (V a) where
show (V a) = if a instanceof Show
then show a
else "Some Error."
How could this behaviour be implemented in Haskell?
As I said in a comment, the runtime objects allocated in memory don't have type tags in a Haskell program. There is therefore no universal instanceof operation like in, say, Java.
It's also important to consider the implications of the following. In Haskell, to a first approximation (i.e., ignoring some fancy stuff that beginners shouldn't tackle too soon), all runtime function calls are monomorphic. I.e., the compiler knows, directly or indirectly, the monomorphic (non-generic) type of every function call in an executable program. Even though your V type's show function has a generic type:
-- Specialized to `V a`
show :: V a -> String -- generic; has variable `a`
...you can't actually write a program that calls the function at runtime without, directly or indirectly, telling the compiler exactly what type a will be in every single call. So for example:
-- Here you tell it directly that `a := Int`
example1 = show (V (1 :: Int))
-- Here you're not saying which type `a` is, but this just "puts off"
-- the decision—for `example2` to be called, *something* in the call
-- graph will have to pick a monomorphic type for `a`.
example2 :: a -> String
example2 x = show (V x) ++ example1
Seen in this light, hopefully you can spot the problem with what you're asking:
instance Show (V a) where
show (V a) = if a instanceof Show
then show a
else "Some Error."
Basically, since the type for the a parameter will be known at compilation time for any actual call to your show function, there's no point to testing for this type at runtime—you can test for it at compilation time! Once you grasp this, you're led to Will Sewell's suggestion:
-- No call to `show (V x)` will compile unless `x` is of a `Show` type.
instance Show a => Show (V a) where ...
EDIT: A more constructive answer perhaps might be this: your V type needs to be a tagged union of multiple cases. This does require using the GADTs extension:
{-# LANGUAGE GADTs #-}
-- This definition requires `GADTs`. It has two constructors:
data V a where
-- The `Showable` constructor can only be used with `Show` types.
Showable :: Show a => a -> V a
-- The `Unshowable` constructor can be used with any type.
Unshowable :: a -> V a
instance Show (V a) where
show (Showable a) = show a
show (Unshowable a) = "Some Error."
But this isn't a runtime check of whether a type is a Show instance—your code is responsible for knowing at compilation time where the Showable constructor is to be used.
You can with this library: https://github.com/mikeizbicki/ifcxt. Being able to call show on a value that may or may not have a Show instance is one of the first examples it gives. This is how you could adapt that for V a:
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
import IfCxt
import Data.Typeable
mkIfCxtInstances ''Show
data V a = V a
instance forall a. IfCxt (Show a) => Show (V a) where
show (V a) = ifCxt (Proxy::Proxy (Show a))
(show a)
"<<unshowable>>"
This is the essence of this library:
class IfCxt cxt where
ifCxt :: proxy cxt -> (cxt => a) -> a -> a
instance {-# OVERLAPPABLE #-} IfCxt cxt where ifCxt _ t f = f
I don't fully understand it, but this is how I think it works:
It doesn't violate the "open world" assumption any more than
instance {-# OVERLAPPABLE #-} Show a where
show _ = "<<unshowable>>"
does. The approach is actually pretty similar to that: adding a default case to fall back on for all types that do not have an instance in scope. However, it adds some indirection to not make a mess of the existing instances (and to allow different functions to specify different defaults). IfCxt works as a a "meta-class", a class on constraints, that indicates whether those instances exist, with a default case that indicates "false.":
instance {-# OVERLAPPABLE #-} IfCxt cxt where ifCxt _ t f = f
It uses TemplateHaskell to generate a long list of instances for that class:
instance {-# OVERLAPS #-} IfCxt (Show Int) where ifCxt _ t f = t
instance {-# OVERLAPS #-} IfCxt (Show Char) where ifCxt _ t f = t
which also implies that any instances that were not in scope when mkIfCxtInstances was called will be considered non-existing.
The proxy cxt argument is used to pass a Constraint to the function, the (cxt => a) argument (I had no idea RankNTypes allowed that) is an argument that can use the constraint cxt, but as long as that argument is unused, the constraint doesn't need to be solved. This is similar to:
f :: (Show (a -> a) => a) -> a -> a
f _ x = x
The proxy argument supplies the constraint, then the IfCxt constraint is solved to either the t or f argument, if it's t then there is some IfCxt instance where this constraint is supplied which means it can be solved directly, if it's f then the constraint is never demanded so it gets dropped.
This solution is imperfect (as new modules can define new Show instances which won't work unless it also calls mkIfCxtInstances), but being able to do that would violate the open world assumption.
Even if you could do this, it would be a bad design. I would recommend adding a Show constraint to a:
instance Show a => Show (V a) where ...
If you want to store members in a container data type that are not an instance of Show, then you should create a new data type fore them.

Is there a way to represent the function unpack on Showable in GHC's Haskell?

I have a type named Showable like this:
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE ExplicitForAll #-}
data Showable = forall a . Show a => Showable a
Then making a function that packs it is trivial. I just have to write:
pack :: forall a . Show a => a -> Showable
pack x = Showable x
However it seems impossible to create the inverse function that would unpack the data from Showable. If I try to just invert what I wrote for pack and write:
unpack :: exists a . Show a => Showable -> a
unpack (Showable x) = x
then I get an error from GHC.
I have looked into the docs on GHC Language extensions and there seems to be no support for the exists keyword. I have seen that it might be possible in some other Haskell compilers, but I would prefer to be able to do it in GHC as well.
Funnily enough, I can still pattern match on Showable and extract the data from inside it in that way. So I could get the value out of it that way, but if I wanted to make a pointfree function involving Showable, then I would need unpack.
So is there some way to implement unpack in GHC's Haskell, maybe using Type Families or some other arcane magic that are GHC extensions?
Your unpack, as you have typed, cannot be written. The reason is that the existential variable a "escapes" the scope of the pattern match and there is no facility to track that behavior. Quote the docs:
data Baz = forall a. Eq a => Baz1 a a
| forall b. Show b => Baz2 b (b -> b)
When pattern matching, each pattern match introduces a new, distinct, type for each existential type variable. These types cannot be unified with any other type, nor can they escape from the scope of the pattern match. For example, these fragments are incorrect:
f1 (MkFoo a f) = a
What is this "a" in the result type? Clearly we don't mean this:
f1 :: forall a. Foo -> a -- Wrong!
The original program is just plain wrong. Here's another sort of error
f2 (Baz1 a b) (Baz1 p q) = a==q
It's ok to say a==b or p==q, but a==q is wrong because it equates the two distinct types arising from the two Baz1 constructors.
You can however rewrite the unpack type equivalently so that the existential does not escape:
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE RankNTypes #-}
module Lib where
data Showable = forall a. Show a => Showable a
pack :: Show a => a -> Showable
pack = Showable
unpack :: Showable -> (forall a. Show a => a -> r) -> r
unpack (Showable a) a2r = a2r a

Using constraint kinds and type families with 'limited' constraints

I'm working on an applicative functor that contains a monoid to "view" the execution. However, sometimes I don't care about this part at all, so the choice of monoid is irrelevant as it will never be consumed. I've simplified what I have into:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
import GHC.Exts
class Render a b where render :: a -> b
instance Render a () where render = const ()
class Merge a where
type Renderer a b :: Constraint
merge :: Renderer a b => a -> b
data Foo = Foo Bool
instance Merge Foo where
type (Renderer Foo) m = (Render Bool m)
merge (Foo b) = render b
Render is used to transform various as into a single b. Merge is a big simplification of my actual functor, but the point is it contains a type family/constraint and my intention of that is to specify exactly what Renderers a Merge requires.
Now, I might want to "run" the Merge, but discard the view, which is akin to something like:
runFoo :: Merge a => a -> Int
runFoo x = case merge x of () -> 5
But this will fail because:
Could not deduce (Renderer a ()) arising from a use of merge
I chose () as my monoid because forall a, we have an instance of Render a (). So if there was a way to say that Merge a just means a collection Render constraints then this would work fine. Of course, Merge a is more general than that - it could add arbitrary constraints, which explains the compilation error.
Is there anyway to achieve what I want without changing the signature of runFoo?
This might not scale if you have a lot of these cases, but this works:
class Renderer a () => Merge a where
...

Resources