List constructor names of a Haskell type? - haskell

conNameOf allows me to display the constructor name of a given piece of data, given that type is an instance of Generic.
What I'd like is something similar. For a given type, I want to get the full list of constructor names. For example:
data Nat = Z | S Nat
deriving (Generic)
-- constrNames (Proxy :: Proxy Nat) == ["Z", "S"]
Does something like constrNames exist? If not, how can I write it?

The function conNames from module Generics.Deriving.ConNames in package generic-deriving provides this functionality. It takes a term of the given type, though its value is not used, so you can use undefined:
{-# LANGUAGE DeriveGeneric #-}
import GHC.Generics
import Generics.Deriving.ConNames
import Data.Proxy
data Nat = Z | S Nat deriving (Generic)
main = print $ conNames (undefined :: Nat)
gives:
λ> main
["Z","S"]

Related

TypeLits or Singletons: Promoting an `Integer` to `KnownNat` (`Nat`) at Runtime

I've found two ways to promote an Integer to a Nat (or KnownNat, I don't get the distintion yet) at runtime, either using TypeLits and Proxy (Data.Proxy and GHC.TypeLits), or Singletons (Data.Singletons). In the code below you can see how each of the two approaches is used:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Main where
import Prelude hiding (replicate)
import Data.Proxy (Proxy(Proxy))
import Data.Monoid ((<>))
import Data.Singletons (SomeSing(..), toSing)
import GHC.TypeLits
import Data.Singletons.TypeLits
import Data.Vector.Sized (Vector, replicate)
main :: IO ()
main = playingWithTypes 8
playingWithTypes :: Integer -> IO ()
playingWithTypes nn = do
case someNatVal nn of
Just (SomeNat (proxy :: Proxy n)) -> do
-- let (num :: Integer) = natVal proxy
-- putStrLn $ "Some num: " <> show num
putStrLn $ "Some vector: " <> show (replicate 5 :: Vector n Int)
Nothing -> putStrLn "There's no number, the integer was not a natural number"
case (toSing nn :: SomeSing Nat) of
SomeSing (SNat :: Sing n) -> do
-- let (num :: Integer) = natVal (Proxy :: Proxy n)
-- putStrLn $ "Some num: " <> show num
putStrLn $ "Some vector: " <> show (replicate 5 :: Vector n Int)
The documentation for TypeLits indicates that it shouldn't be used by developers, but Singletons don't capture the case in which the given Integer is not a natural number (i.e., running playingWithTypes 8 runs without errors, but playingWithTypes (-2) fails when we try to create a Singleton from the non-natural number).
So, what is the "standard" way to promote an Integer to a Nat? Or what is the best approach to promote, using TypeLits and Proxy, or Singletons?
Nat (or KnownNat, I don't get the distintion yet)
Nat is the kind of type-level natural numbers. It has no term-level inhabitants. The idea is that GHC promotes any natural number into the type-level, and gives it kind Nat.
KnownNat is a constraint, on something of kind Nat, whose implementation witnesses how to convert the thing of kind Nat to a term-level Integer. GHC automagically creates instances of KnownNat for all type-level inhabitants of the kind Nat1.
That said, even if every n :: Nat (read type n of kind Nat) has a KnownNat instance on it1, you still need to write out the constraint.
I've found two ways to promote an Integer to a Nat
Have you really? At the end of the day, Nat in today's GHC is simply magical. singletons taps into that same magic. Under the hood, it uses someNatVal.
So, what is the "standard" way to promote an Integer to a Nat? Or what is the best approach to promote, using GHC.TypeLits and Proxy, or singletons?
There is no standard way. My take is: use singletons when you can afford its dependency footprint and GHC.TypeLits otherwise. The advantage of singletons is that the SingI type class makes it convenient to do induction based analysis while still also relying on GHC's special Nat type.
1 As pointed out in the comments, not every inhabitant of the Nat kind has a KnownNat instance. For example, Any Nat :: Nat where Any is the one from GHC.Exts. Only the inhabitants 0, 1, 2, ... have KnownNat instances.

Haskell Export Record for Read Access Only

I have a Haskell type that uses record syntax.
data Foo a = Foo { getDims :: (Int, Int), getData :: [a] }
I don't want to export the Foo value constructor, so that the user can't construct invalid objects. However, I would like to export getDims, so that the user can get the dimensions of the data structure. If I do this
module Data.ModuleName(Foo(getDims)) where
then the user can use getDims to get the dimensions, but the problem is that they can also use record update syntax to update the field.
getDims foo -- This is allowed (as intended)
foo { getDims = (999, 999) } -- But this is also allowed (not intended)
I would like to prevent the latter, as it would put the data in an invalid state. I realize that I could simply not use records.
data Foo a = Foo { getDims_ :: (Int, Int), getData :: [a] }
getDims :: Foo a -> (Int, Int)
getDims = getDims_
But this seems like a rather roundabout way to work around the problem. Is there a way to continue using record syntax while only exporting the record name for read access, not for write access?
Hiding the constructor and then defining new accessor functions for each field is a solution, but it can get tedious for records with a large number of fields.
Here's a solution with the new HasField typeclass in GHC 8.2.1 that avoids having to define functions for each field.
The idea is to define an auxiliary newtype like this:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE PolyKinds #-} -- Important, obscure errors happen without this.
import GHC.Records (HasField(..))
-- Do NOT export the actual constructor!
newtype Moat r = Moat r
-- Export this instead.
moat :: r -> Moat r
moat = Moat
-- If r has a field, Moat r also has that field
instance HasField s r v => HasField s (Moat r) v where
getField (Moat r) = getField #s r
Every field in a record r will be accesible from Moat r, with the following syntax:
λ :set -XDataKinds
λ :set -XTypeApplications
λ getField #"getDims" $ moat (Foo (5,5) ['s'])
(5,5)
The Foo constructor should be hidden from clients. However, the field accessors for Foo should not be hidden; they must be in scope for the HasField instances of Moat to kick in.
Every function in your public-facing api should return and receive Moat Foos instead of Foos.
To make the accessor syntax slightly less verbose, we can turn to OverloadedLabels:
import GHC.OverloadedLabels
newtype Label r v = Label { field :: r -> v }
instance HasField l r v => IsLabel l (Label r v) where
fromLabel = Label (getField #l)
In ghci:
λ :set -XOverloadedLabels
λ field #getDims $ moat (Foo (5,5) ['s'])
(5,5)
Instead of hiding the Foo constructor, another option would be to make Foo completely public and define Moat inside your library, hiding any Moat constructors from clients.

(Generically) Build Parsers from custom data types?

I'm working on a network streaming client that needs to talk to the server. The server encodes the responses in bytestrings, for example, "1\NULJohn\NULTeddy\NUL501\NUL", where '\NUL' is the separator. The above response translates to "This is a message of type 1(hard coded by the server), which tells the client what the ID of a user is(here, the user id of "John Teddy" is "501").
So naively I define a custom data type
data User
{ firstName :: String
, lastName :: String
, id :: Int
}
and a parser for this data type
parseID :: Parser User
parseID = ...
Then one just writes a handler to do some job(e.g., write to a database) after the parser succesfully mathes a response like this. This is very straightforward.
However, the server has almost 100 types of different responses like this that the client needs to parse. I suspect that there must be a much more elegant way to do the job rather than writing 100 almost identical parsers like this, because, after all, all haksell coders are lazy. I am a total newbie to generic programming so can some one tell me if there is a package that can do this job?
For these kinds of problems I turn to generics-sop instead of using generics directly. generics-sop is built on top of Generics and provides functions for manipulating all the fields in a record in a uniform way.
In this answer I use the ReadP parser which comes with base, but any other Applicative parser would do. Some preliminary imports:
{-# language DeriveGeneric #-}
{-# language FlexibleContexts #-}
{-# language FlexibleInstances #-}
{-# language TypeFamilies #-}
{-# language DataKinds #-}
{-# language TypeApplications #-} -- for the Proxy
import Text.ParserCombinators.ReadP (ReadP,readP_to_S)
import Text.ParserCombinators.ReadPrec (readPrec_to_P)
import Text.Read (readPrec)
import Data.Proxy
import qualified GHC.Generics as GHC
import Generics.SOP
We define a typeclass that can produce an Applicative parser for each of its instances. Here we define only the instances for Int and Bool:
class HasSimpleParser c where
getSimpleParser :: ReadP c
instance HasSimpleParser Int where
getSimpleParser = readPrec_to_P readPrec 0
instance HasSimpleParser Bool where
getSimpleParser = readPrec_to_P readPrec 0
Now we define a generic parser for records in which every field has a HasSimpleParser instance:
recParser :: (Generic r, Code r ~ '[xs], All HasSimpleParser xs) => ReadP r
recParser = to . SOP . Z <$> hsequence (hcpure (Proxy #HasSimpleParser) getSimpleParser)
The Code r ~ '[xs], All HasSimpleParser xs constraint means "this type has only one constructor, the list of field types is xs, and all the field types have HasSimpleParser instances".
hcpure constructs an n-ary product (NP) where each component is a parser for the corresponding field of r. (NP products wrap each component in a type constructor, which in our case is the parser type ReadP).
Then we use hsequence to turn a n-ary product of parsers into the parser of an n-ary product.
Finally, we fmap into the resulting parser and turn the n-ary product back into the original r record using to. The Z and SOP constructors are required for turning the n-ary product into the sum-of-products the to function expects.
Ok, let's define an example record and make it an instance of Generics.SOP.Generic:
data Foo = Foo { x :: Int, y :: Bool } deriving (Show, GHC.Generic)
instance Generic Foo -- Generic from generics-sop
Let's check if we can parse Foo with recParser:
main :: IO ()
main = do
print $ readP_to_S (recParser #Foo) "55False"
The result is
[(Foo {x = 55, y = False},"")]
You can write your own parser - but there is already a package that can do the parsing for you: cassava and while SO is usually not a place to search for library recommendations, I want to include this answer for people looking for a solution, but not having the time to implement this themselves and looking for a solution that works out of the box.
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
import Data.Csv
import Data.Vector
import Data.ByteString.Lazy as B
import GHC.Generics
data Person = P { personId :: Int
, firstName :: String
, lastName :: String
} deriving (Eq, Generic, Show)
-- the following are provided by friendly neighborhood Generic
instance FromRecord Person
instance ToRecord Person
main :: IO ()
main = do B.writeFile "test" "1\NULThomas\NULof Aquin"
Right thomas <- decodeWith (DecodeOptions 0) NoHeader <$>
B.readFile "test"
print (thomas :: Vector Person)
Basically cassava allows you to parse all X-separated structures into a Vector, provided you can write down a FromRecord instance (which needs a parseRecord :: Parser … function to work.
Side note on Generic until recently I thought - EVERYTHING - in haskell has a Generic instance, or can derive one. Well this is not the case I wanted to serialize some ThreadId to CSV/JSON and happened to find out unboxed types are not so easily "genericked"!
And before I forget it - when you speak of streaming and server and so on there is cassava-conduit that might be of help.

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.

Haskell -- get TypeRep from concrete type instance

I want to write a function with this type signature:
getTypeRep :: Typeable a => t a -> TypeRep
where the TypeRep will be the type representation for a, not for t a. That is, the compiler should automatically return the correct type representation at any call sites [to getTypeRep], which will have concrete types for a.
To add some context, I want to create a "Dynamic type" data type, with the twist that it will remember the top-level type, but not its parameter. For example, I want to turn MyClass a into Dynamic MyClass, and the above function will be used to create instances of Dynamic MyClass that store a representation of the type parameter a.
Well, how about using scoped type variables to select the inner component:
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE ScopedTypeVariables #-}
import Data.Dynamic
import Data.Typeable
getTypeRep :: forall t a . Typeable a => t a -> TypeRep
getTypeRep _ = typeOf (undefined :: a)
Works for me:
*Main> getTypeRep (Just ())
()
*Main> getTypeRep (Just 7)
Integer
*Main> getTypeRep ([True])
Bool
Interesting design.
On a tangential note to Don's solution, notice that code rarely require ScopedTypeVariables. It just makes the solution cleaner (but less portable). The solution without scoped types is:
{-# LANGUAGE ExplicitForAll #-}
import Data.Typeable
helper :: t a -> a
helper _ = undefined
getTypeRep :: forall t a. Typeable a => t a -> TypeRep
getTypeRep = typeOf . helper
This function (now) exists in Data.Typeable typeRep

Resources