Specialization of singleton parameters - haskell

I'm playing around with specialization of singletons:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
module Data.Test where
data SingBool (b :: Bool) where
STrue :: SingBool 'True
SFalse :: SingBool 'False
sing :: SingBool b -> Bool
sing SFalse = False
sing STrue = True
{-# SPECIALIZE sing :: SingBool 'False -> Bool #-}
This specializes to something like the following:
singSFalse :: SingBool 'False -> Bool
singSFalse SFalse = False
I'd expect it to generate an RHS of singSFalse _ = False instead.
Is that coercion unpacked only to satisfy the type-checker or is there actual runtime overhead involved in that pattern match? I imagine that GHC does not discard the pattern match on the argument to account for bottom, in order not to increase laziness. But I want to be sure before I begin to model this through Proxy + a SingI-style type class.

OK, to mostly answer my own question: Knowing that SingBool 'False only has one inhabitant is not enough for GHC to get rid of the pattern match, because we could call the function like singSFalse (error "matched"), e.g. bottom is always another inhabitant.
So, specialization (e.g. inlining based on concrete TypeApplications) does not really work well with singletons (turning those type applications into presumably constant value applications) in Haskell (lazy, non-total) w.r.t. zero cost abstractions.
However, by using a SingI-style type class with a proxy (e.g. singByProxy), we don't have the same problems:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MagicHash #-}
module Data.Test where
import GHC.Exts (Proxy#)
class SingIBool (b :: Bool) where
sing :: Proxy# b -> Bool
instance SingIBool 'False where
sing _ = False
instance SingIBool 'True where
sing _ = True
refurbulate :: SingIBool b => Proxy# b -> Int
refurbulate p
| sing p = 0
| otherwise = 1
The specialization refurbulate #(Proxy# 'False) will not only be implemented as const False, also there will not be passed any Proxy# argument at the value level, so it's rather coerce False :: Proxy# -> Bool. Neat! However, I don't get to use singletons in the real world :(
To recap why singletons fail (to get optimized) and type classes work:
By specializing the type class instance, we get to know the RHS of sing, from which we can deduce totality.
By specializing the singleton, we get to know what value the parameter evaluates to, if evaluation terminates.
Knowing the canonical RHS of a type class method x :: () is more informative than just knowing that a parameter x :: () can only evaluate to one value in a non-total, lazy (e.g. Haskell's) setting.

Related

How to create a well-typed function that returns two different types?

I'm highly interested in compiling Formality-Core modules to Haskell libraries. While I could use unsafeCoerce everywhere, it would be more interesting if I could preserve the type information, allowing compiled modules to be published on Cabal and used by other Haskell projects. The problem is that dependent types allow programs that are forbidden by Haskell. For example, the function foo below:
foo: (b : Bool) -> If(b)(Nat)(Bool)
(b)
b<(b) If(b)(Nat)(Bool)>
| zero;
| false;
Returns a different type depending on the input. If the input is false, it returns the number zero. If the input is true, it returns the boolean false. It seems like a function like this can't be translated to Haskell. I believe that, on the last years, Haskell has made good progress towards dependent type, so, I wonder: is there any way to write functions that return different types based on the input value?
GADTs + TypeFamilies (optionally, + DataKinds) can do roughly this. So:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeFamilies #-}
data GADTBool a where
GADTFalse :: GADTBool False
GADTTrue :: GADTBool True
type family If cond t f where
If False t f = f
If True t f = t
foo :: GADTBool b -> If b Int Bool
foo GADTTrue = 0
foo GADTFalse = False
Of course, you'll probably actually want foo :: GADTBool b -> If b (GADTInt 0) (GADTBool False) if you plan to do this kind of thing pervasively. The search term you want for seeing more examples of this kind of hackery is "singleton types", often abbreviated just "singletons".
The state of the art remains the singleton approach.
data SBool b where
SFalse :: SBool 'False
STrue :: SBool 'True
type family If (b :: Bool) (t1 :: k) (t2 :: k) :: k where
If 'False x _ = x
If 'True _ y = y
foo :: SBool b -> If b Natural Bool
foo SFalse = 0
foo STrue = False
It's maybe worth noting that, as a practical matter, the singletons library can be used to take care of most of the boilerplate. So, you can write:
{-# LANGUAGE GADTs #-}
module Formality where
import Numeric.Natural
import Data.Singletons.Prelude
foo :: SBool b -> If b Bool Natural
foo SFalse = 0
foo STrue = False
using almost exactly the syntax used by #dfeuer, up to the order of arguments to If.
The main disadvantage of the singletons library is that any serious type dependent programming is going to eventually require understanding how things are actually implemented internally, and the guts of the library are complicated and not very well documented.
You may find it helpful to start by hand-compiling some Formality using a from-scratch solution using your own singleton GADTs and type families (as in the other answers), and then try to convert it over to use singletons.

How to safely case on kind-constrained type variable in Haskell?

Question
I want to case on a type variable that is restricted to finitely many possibilities due to a kind constraint. And I want to know statically that casing will always discover one of these finitely many possibilities. I can't figure out how to write this case without an unreachable catch-all.
As a concrete example, suppose I have a data kind
data{-kind-} Temp = Hot | Cold
Then my goal is write a function like caseTemp below that determines the Temp a given Temp-kinded type. Something like
data CaseTemp (t :: Temp) where
IsHot :: CaseTemp 'Hot
IsCold :: CaseTemp 'Cold
caseTemp :: forall (t :: Temp). CaseTemp t
caseTemp = ???
I'm OK with having some extra constraints on caseTemp, like the Typeable t in my failed attempt below. Or even with an entirely different approach.
Failed Solution Attempt
Here is my best attempt, but it includes a branch that I think should be unreachable, and that would allow caseTemp to break silently if I added another constructor to Temp (tested in GHC 8.0.2):
{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE StandaloneDeriving #-}
module SOQuestion where
import Data.Typeable ( (:~:)(..), Typeable, eqT )
data{-kind-} Temp = Hot | Cold
data CaseTemp (t :: Temp) where
IsHot :: CaseTemp 'Hot
IsCold :: CaseTemp 'Cold
deriving instance Show (CaseTemp t)
caseTemp :: forall (t :: Temp). Typeable t => CaseTemp t
caseTemp =
case eqT :: Maybe (t :~: 'Hot) of
Just Refl -> IsHot
Nothing -> case eqT :: Maybe (t :~: 'Cold) of
-- (GHC says this "pattern match is redundant" ???
-- Sounds like a bug!)
Just Refl -> IsCold
-- MY QUESTION: is there a way to eliminate the
-- unreachable branch here?
Nothing -> error "Unreachable!"
The problem with this attempt is that GHC believes the Nothing -> error "Unreachable!" branch is reachable.
Updates
User #Alec mentions that Any :: Temp is a fundamental reason that it's impossible to do what I want, since e.g.
import GHC.Prim ( Any )
[...]
badCase :: CaseTemp Any
badCase = undefined :: CaseTemp Any
is accepted by GHC. However, Any is not Typeable, so it's not clear to me that putting constraints on caseTemp couldn't work around this.
There isn't a direct way, because when eqT returns Nothing it doesn't come with a disequality proof.
How about using a type class?
class IsTemp (b :: Temp) where
caseTemp :: CaseTemp b

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.

Haskell - Ambiguous type variable

I couldn't find an answer to my question among several ambiguous type variable error questions.
Basically I want to take type information to the value level. The last line in this example fails.
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeOperators #-}
module Test where
data Typ = TInteger | TString deriving Show
data Empty = Empty
data a ## b = Cons a b
class Typical a b | a -> b where
typical :: a -> b
instance Typical Empty [Typ] where
typical _ = []
instance Typical Integer Typ where
typical _ = TInteger
instance Typical String Typ where
typical _ = TString
instance (Typical a Typ, Typical b [Typ]) => Typical (a ## b) [Typ] where
typical _ = typical (undefined :: a) : typical (undefined :: b)
Here is the first error message:
Test.hs:27:17:
Could not deduce (Typical a0 Typ) arising from a use of `typical'
from the context (Typical a Typ, Typical b [Typ])
bound by the instance declaration at Test.hs:26:10-67
The type variable `a0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Note: there are several potential instances:
instance Typical String Typ -- Defined at Test.hs:23:10
instance Typical Integer Typ -- Defined at Test.hs:20:10
Possible fix: add an instance declaration for (Typical a0 Typ)
In the first argument of `(:)', namely `typical (undefined :: a)'
In the expression:
typical (undefined :: a) : typical (undefined :: b)
In an equation for `typical':
typical _ = typical (undefined :: a) : typical (undefined :: b)
I just don't get it.
What is a0 here? Could it be that the a from my last line is not identified with that from the 2nd last line?
Where should I put a type signature and why?
Please enlighten me!
Ok, I have a solution, but I don't know if this is the cleanest workaround.
Adding {-# LANGUAGE ScopedTypeVariables #-} makes the code compile. This makes it possible to identify a0 with a from the error message (corresponding to the as from the last two lines of the code).
Please comment!

Is it possible to get the Kind of a Type Constructor in Haskell?

I am working with Data.Typeable and in particular I want to be able to generate correct types of a particular kind (say *). The problem that I'm running into is that TypeRep allows us to do the following (working with the version in GHC 7.8):
let maybeType = typeRep (Proxy :: Proxy Maybe)
let maybeCon = fst (splitTyConApp maybeType)
let badType = mkTyConApp maybeCon [maybeType]
Here badType is in a sense the representation of the type Maybe Maybe, which is not a valid type of any Kind:
> :k Maybe (Maybe)
<interactive>:1:8:
Expecting one more argument to ‘Maybe’
The first argument of ‘Maybe’ should have kind ‘*’,
but ‘Maybe’ has kind ‘* -> *’
In a type in a GHCi command: Maybe (Maybe)
I'm not looking for enforcing this at type level, but I would like to be able to write a program that is smart enough to avoid constructing such types at runtime. I can do this with data-level terms with TypeRep. Ideally, I would have something like
data KindRep = Star | KFun KindRep KindRep
and have a function kindOf with kindOf Int = Star (probably really kindOf (Proxy :: Proxy Int) = Star) and kindOf Maybe = KFun Star Star, so that I could "kind-check" my TypeRep value.
I think I can do this manually with a polykinded typeclass like Typeable, but I'd prefer to not have to write my own instances for everything. I'd also prefer to not revert to GHC 7.6 and use the fact that there are separate type classes for Typeable types of different kinds. I am open to methods that get this information from GHC.
We can get the kind of a type, but we need to throw a whole host of language extensions at GHC to do so, including the (in this case) exceeding questionable UndecidableInstances and AllowAmbiguousTypes.
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
import Data.Proxy
Using your definition for a KindRep
data KindRep = Star | KFun KindRep KindRep
we define the class of Kindable things whose kind can be determined
class Kindable x where
kindOf :: p x -> KindRep
The first instance for this is easy, everything of kind * is Kindable:
instance Kindable (a :: *) where
kindOf _ = Star
Getting the kind of higher-kinded types is hard. We will try to say that if we can find the kind of its argument and the kind of the result of applying it to an argument, we can figure out its kind. Unfortunately, since it doesn't have an argument, we don't know what type its argument will be; this is why we need AllowAmbiguousTypes.
instance (Kindable a, Kindable (f a)) => Kindable f where
kindOf _ = KFun (kindOf (Proxy :: Proxy a)) (kindOf (Proxy :: Proxy (f a)))
Combined, these definitions allow us to write things like
kindOf (Proxy :: Proxy Int) = Star
kindOf (Proxy :: Proxy Maybe) = KFun Star Star
kindOf (Proxy :: Proxy (,)) = KFun Star (KFun Star Star)
kindOf (Proxy :: Proxy StateT) = KFun Star (KFun (KFun Star Star) (KFun Star Star))
Just don't try to determine the kind of a polykinded type like Proxy
kindOf (Proxy :: Proxy Proxy)
which fortunately results in a compiler error in only a finite amount of time.

Resources