How to export type constructors when using DataKinds extension? - haskell

Playing with advanced type-system stuff. I want to have named kind and a
couple of type constructors that produce types of that kind:
{-# LANGUAGE DataKinds #-}
data Subject = New | Existing
Here, as I understand, we have named kind Subject and type constructors
New and Existing that are :: Subject. These type constructors do not
take arguments (I plan to use them as phantom types), it should be roughly
equivalent to:
{-# LANGUAGE EmptyDataDecls #-}
data New
data Existing
With the difference that now I can write:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
-- …
data MyConfig :: Subject -> * -> * where
MyConfig
{ mcOneThing :: Path t File
} :: MyConfig k t
This even compiles. What is confusing is that declaration of data kinds is
indistinguishable from data type declarations, so this code seems to produce
data type Subject as well as named kind Subject (?) It would be clearer
for me it we could specify on which level do we declare things (kinds, and
then New and Existing are type constructors; or types, and then New
and Existing are value constructors for things of Subject type). I don't
get this design decision with “promote everything that seems to work”.
Now, my problem is that I cannot export New and Existing as
type-constructors to use in other module, e.g. to declare things like:
foo :: MyConfig New Dir -> …
where at the same time
foo :: MyConfig Int Dir -> …
should be ill-kinded and it should not compile.
Here is how I'm trying to export them:
module MyModule
( New
, Existing
-- …
)
where
What I get:
Not in scope type constructor or class ‘New’
Not in scope type constructor or class ‘Existing’
GHC manual in
section 7.9.3
says that to distinguish between “types and constructors” one can use single quote ', so I tried:
module MyModule
( 'New
, 'Existing
-- …
)
where
…but now it's a parse error.
How do I export New and Existing type constructors, and most
importantly, is there anything wrong with my current understanding?

Use the usual syntax for exporting constructors:
module MyModule (Subject(..)) where
data Subject = New | Existing
Currently, lifted and unlifted constructors are tied together, so we can only export/import them together.
Also, you don't need to have DataKinds in MyModule, only in the module where you intend to use lifted constructors.

Related

Automatically generating `PersistEntity` for pre-existing types

Motivation: I want to use MongoDB to store data. The persistent library seems to be the only high level Haskell library supporting MongoDB. My project has already defined types representing the rows (documents) of any database.
Typical use of persistent is to define your type via a bit of template Haskell, as such:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
import Database.Persist
import Database.Persist.TH
import Database.Persist.Sqlite
import Control.Monad.IO.Class (liftIO)
mkPersist mongoSettings [persistLowerCase|
Person
name String
age Int
deriving Show
|]
However, I already have significant sized types in code akin to:
newtype Name = Name String deriving (Show, Etc, Etc)
data Person = Person
{ name :: Name, age :: Int } deriving (Show, Etc, Etc)
So ideally I'd get my PersistEntity and maybe even PersistField instances via a slimmed down bit of TH such as:
mkPersistFromType mongoSettings ''Person
However, there is no TH function like mkPersistFromType. Writing the class instances by hand is tedious - they are extremely long. What is the right way forward? Is there a mkPersistFromType somewhere I haven't seen or should I just write that myself?
Note that mkPersist is just a function, and it returns a list of declarations to be added to the source file. So you are free to post-process this declarations and e.g. remove unwanted ones.
Here is an example where I filter out all data declarations:
myMkPersist settings = do
filter wanted <$> mkPersist settings [persistLowerCase|
Person
name String
|]
where
wanted DataD{} = False
wanted _ = True
Note that myMkPersist should be defined in a separate file due to the stage restriction. In the main file you use this function:
data Person = Person
{ personName :: String
}
myMkPersist mongoSettings
Also you may want to check the output on the mkPersist to see how exactly you want to post-process the declarations, you can do that using -ddump-splices cli option.

how to define a class with a type family [duplicate]

This question already has an answer here:
How to make lenses for records with type-families [duplicate]
(1 answer)
Closed 3 years ago.
The following code generates an "Expected a constraint" error :
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ExistentialQuantification #-}
type family Note a
type instance Note String = String
data SomeNote = forall a. Note a => SomeNote a
class HasNote b where
noteOf :: b -> SomeNote
The error is Expected a constraint, but 'Note a' has kind '*', in the definition of SomeNote. Why ? How can I fix it ?
The goal is to include an instance of the Note type family in some data structure b, and use noteOf b to extract it, whatever the instance is.
The goal is to include an instance of the Note type family in some data structure b, and use noteOf b to extract it
That's not how type families work. All you've really said is that you can map one type, represented by variable a into another type via the type function Note. It doesn't mean values of type a contain a value of type Note b at all. It is the type class that rather strongly implies the Note a type is within or computable from the a type.
The code is along the lines of:
type family Note a
type instance Note String = String
class SomeNote a where
noteOf :: a -> Note a
Even better, consider using an associated type:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
class SomeNote a where
type Note a :: *
noteOf :: a -> Note a
instance SomeNote String where
type Note String = String
noteOf = id

Haskell: type classes: multiple inheritance example

I came to know that we can achieve multiple inheritance using type classes. I had written small haskell code, but unable to figure out the problem.
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE StandaloneDeriving #-}
class (Eq a, Show a) => C a where
getHashCode :: a -> Integer
getHashCode obj = 123
type Id = Int
type Name = String
data Employee = Employee Id Name deriving C
When i tried to load above code, I am getting following error. Any help on this.
No instance for (Eq Employee)
arising from the 'deriving' clause of a data type declaration
Possible fix:
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (C Employee)
Failed, modules loaded: none.
I searched google some time, but unable to found good example for multiple inheritance. it will be helpful if you provide some info, example on multiple inheritance in Haskell.
Reference: https://www.haskell.org/tutorial/classes.html
Saying
class (Eq a, Show a) => C a where
does not mean that types that implement C automatically implement Eq and Show, it means that they must first implement Eq and Show before they can implement C.
A class in Haskell is not the same as a class in Java, either, it's closer to an interface, but it can't be used in the same ways (and shouldn't). Haskell doesn't actually have a concept of inheritance or classes in the OOP sense, as it's not an OOP language.
However, if you want to have Eq and Show instances automatically for a type, just add them to the deriving clause of the data type.

Existential quantifier silently disrupts Template Haskell (makeLenses). Why?

I have this file:
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ExistentialQuantification #-}
module Toy where
import Control.Lens
data Bar = Bar { _barish :: String }
data Foo = forall a. Show a => Foo { _fooish :: a }
$(makeLenses ''Bar)
$(makeLenses ''Foo)
x = barish
y = fooish
and I get the following error message:
Toy.hs:15:5:
Not in scope: `fooish'
Perhaps you meant `_fooish' (line 9)
This is my first time attempting to use existential quantifiers; I have no idea why this combination of features breaks. Even more worryingly, why do I get no error message about makeLenses failing? I ran runhaskell Toy.hs
You can't actually use your function _fooish. If you try to do that, you get the error:
Cannot use record selector `_fooish' as a function due to escaped type variables
Probable fix: use pattern-matching syntax instead
In the expression: _fooish
So lens can't generate a lens for you. Why doesn't it give an error? Well, sometimes you have additional fields for which it's possible to generate lenses. It seems this not the case here, but I think in general makeLenses just skips everything that is impossible to do and tries to generate the rest.

Undefined at the type level

Often when I'm playing with Haskell code, I stub things out with a type annotation and undefined.
foo :: String -> Int
foo = undefined
Is there a type-level "undefined" that I could use in a similar way?
(Ideally, in conjunction with a kind annotation)
type Foo :: * -> *
type Foo = Undefined
Further thought on the same thread: is there a way for me to stub out typeclass instances for types created this way? An even easier way than the following theoretical way?
instance Monad Foo where
return = undefined
(>>=) = undefined
You can use EmptyDataDecls to stub out a type, and with KindSignatures you can give it a kind:
{-# LANGUAGE EmptyDataDecls, KindSignatures #-}
data Foo :: * -> *
You can also stub out the Monad instance without warnings with this option to GHC.
{-# OPTIONS_GHC -fno-warn-missing-methods #-}
instance Monad Foo
And then you don't need to leave any implementation for return and >>=.
This question was asked and answered a long time ago; best practices have evolved since.
These days, instead of undefined, for stubbing out code you should be using typed holes, and their type-level analogue, partial type signatures.

Resources