What is wrong with my data constructor import/use, when ghc suggestion is to add constructor to import list? - haskell

I have the following line of code where I'm trying to extract the internal raw type so I can work with it directly:
SDL.Internal.Types.Window (rawWindow) = window
My import looks like:
import qualified SDL.Internal.Types (Window)
The error I get is below; it seems I'm already doing what it suggests.
% /home/brandon/workspace/hico/src/Hico/Game.hs:273:5: error:
Not in scope: data constructor `SDL.Internal.Types.Window'
Perhaps you want to add `Window' to the import list
in the import of `SDL.Internal.Types' (src/Hico/Game.hs:34:1-48).
|
273 | SDL.Internal.Types.Window (rawWindow) = window
| ^^^^^^^^^^^^^^^^^^^^^^^^^
The content of the Types.hs file is very short, and doesn't seem to offer any clues to me:
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module SDL.Internal.Types
( Joystick(..)
, Window(..)
, Renderer(..)
) where
import Data.Data (Data)
import Data.Typeable
import GHC.Generics (Generic)
import qualified SDL.Raw as Raw
newtype Joystick = Joystick { joystickPtr :: Raw.Joystick }
deriving (Data, Eq, Generic, Ord, Show, Typeable)
newtype Window = Window (Raw.Window)
deriving (Data, Eq, Generic, Ord, Show, Typeable)
-- | An SDL rendering device. This can be created with 'SDL.Video.createRenderer'.
newtype Renderer = Renderer Raw.Renderer
deriving (Data, Eq, Generic, Ord, Show, Typeable)

By writing
import qualified SDL.Internal.Types (Window)
you are importing only the type Window, and none of its constructors. To import a data type and some limited subset of its constructors, one writes (using Maybe as an example because I don't know SDL's types):
import Prelude (Maybe(Just))
This import would allow you to use Maybe in type annotations, and use the Just constructor to pattern-match or to create new values of type Maybe a, but you would not be able to use Nothing in either of those circumstances.
Note that the above would be a very unusual thing to do: normally you want either all of a type's constructors (so that you can build and consume any value of that type), or none of them (so that your functions can receive or return values of that type, constructed and consumed by other functions).
If you want all of a type's constructors, you can use the exact syntax used in the module export definition you listed: (..) means "all of the constructors of this type":
import qualified SDL.Internal.Types (Window(..))

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.

deriving clause with arbitrary "Constraint aliases"?

For example, this declaration with deriving:
{-# LANGUAGE DeriveDataTypeable, ConstraintKinds #-}
import Data.Data (Data)
import Data.Typeable (Typeable)
type Constraints a = (Show a, Eq a, Ord a, Data a, Typeable a)
data A = A deriving (Constraints)
errors with:
Illegal deriving item ‘Constraints’
Which makes sense given http://downloads.haskell.org/~ghc/7.8.3/docs/html/users_guide/deriving.html
I write deriving (Show, Eq, Ord, Data, Typeable) for most of my types. It might be nice to export standard "constraint aliases", i.e. any type of kind * -> Constraint. Given, of course, that the constraints in the constraint tuple are all the right arity, have an empty "minimal complete definition", etc.
Is there any proposal for this? How hard would it be? Are there alternatives?
There is no proposal for this. It wouldn't be too hard, but I suspect it wouldn't get a lot of traction. Not only could you use template haskell to generate standalone deriving declarations as a comment suggests, but you could macro-expand to your desired clause using CPP if you really want.

Is it possible to construct a new record using Lenses?

If I have a record type with lenses, is it possible to construct a new record without using the underlying record accessors?
{-# LANGUAGE TemplateHaskell #-}
import Control.Lens
import Control.Lens.TH
data Foo = Foo { _s :: String
, _b :: Bool
} deriving (Show, Eq)
makeLenses ''Foo
I could make Foo an instance of Data.Default and then modifiy def with lenses, but not all record types will have sensible defaults. Does Control.Lens have its own way to do it?
No, there is currently no way to do that. You'll have to use something like Foo{} as default or not use lens for record construction. However, there is already an issue in lens covering this.

Why can data type not be serialized although it is member of the show class?

data Mine = Firstname String
| Lastname String
deriving (Show, Serialize)
This does not compile and gives the error
Not in scope: type constructor or class `Serialize'
Why is this not seen as member of the Serialize class although it is member of the Show class. I thought that all members of the Show class should serialize without problems?
That error is saying that the Serialize typeclass is not in scope. You need to import the package that defines the typeclass in order to use it. You probably want:
import Data.Serialize
from the cereal package.
If you do want to automatically derive Serialize for your class, you can do it like this:
{-# LANGUAGE DeriveGeneric #-}
import Data.Serialize (Serialize)
import GHC.Generics (Generic)
data Mine = Firstname String
| Lastname String
deriving (Show, Generic)
instance Serialize Mine

Explicitly import instances

How do I explicitly import typeclass instances? Also, how do I do this with a qualified import?
Currently, I'm doing
import Control.Monad.Error ()
to import the monad instance that I can use for (Either String). Previously, I used
import Control.Monad.Error
I'm not satisfied with either one, because the Monad instance is implicitly imported.
The inability to control imports of instances is one of the trade-offs the Haskell typeclass system makes. Here's an example in a hypothetical Haskell dialect where you can:
Foo.hs:
module Foo where
data Foo = FooA | FooB deriving (Eq, Ord)
Bar.hs:
module Bar (myMap) where
import Data.Map (Map)
import qualified Data.Map as Map
import Foo
myMap :: Map Foo Int
myMap = Map.singleton FooA 42
Baz.hs:
module Baz where
import Data.Map (Map)
import qualified Data.Map as Map
import Foo hiding (instance Ord Foo)
import Bar (myMap)
instance Ord Foo where
FooA > FooB = True
FooB > FooA = False
ouch :: Map Foo Int
ouch = Map.insert FooB 42 myMap
Yikes! The set myMap was created with the proper instance Ord Foo, but it's being combined with a map created with a different, contradictory instance.
Being able to do this would violate Haskell's open world assumption. Unfortunately, I don't know of a good, centralised resource for learning about it. This section of RWH might be helpful (I searched for "haskell open world assumption").
You can't. Instances are always implicitly exported and hence you can't explicitly import them. By the way, Either e's Monad instance is nowadays in Control.Monad.Instances.
Although the generally correct answer would be "no, you can't", I suggest this horrendous solution:
copy + paste
Take a look at the library source code for the desired module, and copy/paste the necessary data declarations, imports, and function definitions into your own code. Don't copy the instances you don't want.
Depending on the problem at hand, the ghc type system extensions OverlappingInstances or IncoherentInstances might be an alternate solution, though this probably won't solve any problems with the base libraries.

Resources