FromRow for my data which isn't polymorphic: - haskell

I'm trying to create an instance for my data which isn't polymorphic:
import Database.PostgreSQL.Simple
import Database.PostgreSQL.Simple.FromRow
data MyData = A | B | C
instance FromRow MyData where
fromRow = MyData <$> field -- doesn't compile
But it doesn't compile.
UPDATE:
I can't get it to compile
instance FromField MyData where
fromField f mbs =
case mbs of
Just val -> A --????
Nothing -> returnError ConversionFailed f "error"
This throws an error Couldn't match expected type ‘Conversion MyData with actual type MyData
How to make it return Conversion MyData?

You need to come up with
fromRow :: RowParser MyData
You have
field :: FromField a => RowParser a
which makes a RowParser (a fragment of a parser for a row) for any FromField instance.
You could write
fromRow = field
to parse single-field rows as MyData. However, your MyData type doesn't really look like the sort of thing that should have a FromRow instance at all. It should probably have (only) a FromField instance.
The biggest technical problem with your current code is that you're trying to map a type constructor over something. You can only map functions (including data constructors and record field accessors).
Response to update
You might want
instance FromField MyData where
fromField f mbs = do
char <- fromField f mbs
case char of
'A' -> pure A
'B' -> pure B
'C' -> pure C
_ -> returnError ConversionFailed f [char]
This should work if you're trying to convert the contents of a field containing a character to your type. If you're dealing with a different sort of field format, you may have to make adjustments.
This is a very common approach to using parser combinator libraries. Instead of building a parser for your type from scratch, you should usually look first to see if the library offers parsers for a similar type, or components of your type. You can then use the standard Functor, Applicative, and Monad operations, as well as any special ones the library provides, to build your parser on top.

Related

Is there a way to prevent Data.Generics.Alloy.GenInstances from scanning Data.Text.Internal?

I need to do transformations on an AST; here's a portion of the AST:
data Expr
= BinExpr { beOp :: BinaryOp
, beLeft :: Expr
, beRight :: Expr }
| Name Text
| IntegerLit Integer
| StringLit Text
deriving (Data, Typeable)
And this is a fairly complex AST, so there are many types involved.
I'm using alloy to generate the generic transformations, specifically:
autoGen :: IO ()
autoGen = do
createDirectoryIfMissing True baseDir
writeInstancesTo inst doc imports targetFile
where
inst = allInstances GenWithoutOverlapped
doc = [genInstance (undefined :: Doc)]
imports = header ++ instanceImports
Now, this was fine when using String, but I'm trying to migrate to Data.Text. When the code generation runs, it's reading into the internals of Data.Text like so:
instance (Alloy ([(GHC.Types.Char)]) (f :- ops) BaseOp) =>
Alloy ((Data.Text.Internal.Text)) BaseOp (f :- ops) where
transform _ ops (Data.Text.Internal.pack a0)
= Data.Text.Internal.pack
(transform ops BaseOp (a0))
I believe pack is tied to GHC internals so that's not a valid pattern match, and regardless, having the code mucking with the internals of a Data.Text is liable to break the invariants. (Edit: it looks like there's an instance Data Text where gfoldl f z txt = z packf(unpack txt) declaration, but regardless, I don't need/want to traverse Text values.)
Is there a way to force Alloy to treat a type as atomic? I'm hoping to avoid a newtype to wrap Text as all the code working with ASTs would need to deal with it, which rather defeats the purpose of using generics to avoid boilerplate.
Maybe try this trick: we parameterize the Expr type to override the Data instance used for Text when deriving instances with alloy.
data Expr_ text
= BinExpr { beOp :: BinaryOp
, beLeft :: Expr_ text
, beRight :: Expr_ text }
| Name text
...
| StringLit text
The rest of the code base can use this synonym, hopefully without breaking too much with type inference issues.
type Expr = Expr_ Text
But for Data-generic operations, we use a newtype wrapper around Text and make it behave like a nullary constructor, hoping alloy doesn't need the result of gunfold (or perhaps you could make it behave like a string using pattern synonyms).
newtype DataText = DataText Text
instance Data DataText where
gunfold _ f _ = f undefined
...
autoGen will then specialize everything at DummyText.
Use Data.Coerce.coerce to easily convert between functions on Expr_ DataText and Expr.
coerce :: Expr_ DataText -> Expr
coerce :: Expr -> Expr_ DataText
coerce :: (Expr_ DataText -> Expr_ DataText) -> Expr -> Expr
This might be used to write instances of alloy's type classes for Expr, based on the instances that were derived from you. It's a bit of boilerplate, but hopefully it can be contained and hidden without affecting the rest of the code.

Is it possible to ensure that two GADT type variables are the same without dependent types?

I'm writing a compiler where I'm using GADTs for my IR but standard data types for my everything else. I'm having trouble during the conversion from the old data type to the GADT. I've attempted to recreate the situation with a smaller/simplified language below.
To start with, I have the following data types:
data OldLVal = VarOL Int -- The nth variable. Can be used to construct a Temp later.
| LDeref OldLVal
data Exp = Var Int -- See above
| IntT Int32
| Deref Exp
data Statement = AssignStmt OldLVal Exp
| ...
I want to convert these into this intermediate form:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
-- Note: this is a Phantom type
data Temp a = Temp Int
data Type = IntT
| PtrT Type
data Command where
Assign :: NewLVal a -> Pure a -> Command
...
data NewLVal :: Type -> * where
VarNL :: Temp a -> NewLVal a
DerefNL :: NewLVal ('PtrT ('Just a)) -> NewLVal a
data Pure :: Type -> * where
ConstP :: Int32 -> Pure 'IntT
ConstPtrP :: Int32 -> Pure ('PtrT a)
VarP :: Temp a -> Pure a
At this point, I just want to write a conversion from the old data type to the new GADT. For right now, I have something that looks like this.
convert :: Statement -> Either String Command
convert (AssignStmt oldLval exp) = do
newLval <- convertLVal oldLval -- Either String (NewLVal a)
pure <- convertPure exp -- Either String (Pure b)
-- return $ Assign newLval pure -- Obvious failure. Can't ensure a ~ b.
pure' <- matchType newLval pure -- Either String (Pure a)
return $ Assign newLval pure'
-- Converts Pure b into Pure a. Should essentially be a noop, but simply
-- proves that it is possible.
matchType :: NewLVal a -> Pure b -> Either String (Pure a)
matchType = undefined
I realized that I couldn't write convert trivially, so I attempted to solve the problem using this idea of matchType which acts as a proof that these two types are indeed equal. The question is: how do I actually write matchType? This would be much easier if I had fully dependent types (or so I'm told), but can I finish this code here?
An alternative to this would be to somehow provide newLval as an argument to convertPure, but I think that essentially is just attempting to use dependent types.
Any other suggestions are welcome.
If it helps, I also have a function that can convert an Exp or OldLVal to its type:
class Typed a where
typeOf :: a -> Type
instance Typed Exp where
...
instance Typed OldLVal where
...
EDIT:
Thanks to the excellent answers below, I've been able to finish writing this module.
I ended up using the singletons package mentioned below. It was a little strange at first, but I found it pretty reasonable to use after I started understanding what I was doing. However, I did run into one pitfall: The type of convertLVal and convertPure requires an existential to express.
data WrappedPure = forall a. WrappedPure (Pure a, SType a)
data WrappedLVal = forall a. WrappedLVal (NewLVal a, SType a)
convertPure :: Exp -> Either String WrappedPure
convertLVal :: OldLVal -> Either String WrappedLVal
This means that you'll have to unwrap that existential in convert, but otherwise, the answers below show you the way. Thanks so much once again.
You want to perform a comparison at runtime on some type level data (namely the Types by which your values are indexed). But by the time you run your code, and the values start to interact, the types are long gone. They're erased by the compiler, in the name of producing efficient code. So you need to manually reconstruct the type level data that was erased, using a value which reminds you of the type you'd forgotten you were looking at. You need a singleton copy of Type.
data SType t where
SIntT :: SType IntT
SPtrT :: SType t -> SType (PtrT t)
Members of SType look like members of Type - compare the structure of a value like SPtrT (SPtrT SIntT) with that of PtrT (PtrT IntT) - but they're indexed by the (type-level) Types that they resemble. For each t :: Type there's precisely one SType t (hence the name singleton), and because SType is a GADT, pattern matching on an SType t tells the type checker about the t. Singletons span the otherwise strictly-enforced separation between types and values.
So when you're constructing your typed tree, you need to track the runtime STypes of your values and compare them when necessary. (This basically amounts to writing a partially verified type checker.) There's a class in Data.Type.Equality containing a function which compares two singletons and tells you whether their indexes match or not.
instance TestEquality SType where
-- testEquality :: SType t1 -> SType t2 -> Maybe (t1 :~: t2)
testEquality SIntT SIntT = Just Refl
testEquality (SPtrT t1) (SPtrT t2)
| Just Refl <- testEquality t1 t2 = Just Refl
testEquality _ _ = Nothing
Applying this in your convert function looks roughly like this:
convert :: Statement -> Either String Command
convert (AssignStmt oldLval exp) = do
(newLval, newLValSType) <- convertLVal oldLval
(pure, pureSType) <- convertPure exp
case testEquality newLValSType pureSType of
Just Refl -> return $ Assign newLval pure'
Nothing -> Left "type mismatch"
There actually aren't a whole lot of dependently typed programs you can't fake up with TypeInType and singletons (are there any?), but it's a real hassle to duplicate all of your datatypes in both "normal" and "singleton" form. (The duplication gets even worse if you want to pass singletons around implicitly - see Hasochism for the details.) The singletons package can generate much of the boilerplate for you, but it doesn't really alleviate the pain caused by duplicating the concepts themselves. That's why people want to add real dependent types to Haskell, but we're a good few years away from that yet.
The new Type.Reflection module contains a rewritten Typeable class. Its TypeRep is GADT-like and can act as a sort of "universal singleton". But programming with it is even more awkward than programming with singletons, in my opinion.
matchType as written is not possible to implement, but the idea you are going for is definitely possible. Do you know about Data.Typeable? Typeable is a class that provides some basic reflective operations for inspecting types. To use it, you need a Typeable a constraint in scope for any type variable a you want to know about. So for matchType you would have
matchType :: (Typeable a, Typeable b) => NewLVal a -> Pure b -> Either String (Pure a)
It needs also to infect your GADTs any time you want to hide a type variable:
data Command where
Assign :: (Typeable a) => NewLVal a -> Pure a -> Command
...
But if you have the appropriate constraints in scope, you can use eqT to make type-safe runtime type comparisons. For example
-- using ScopedTypeVariables and TypeApplications
matchType :: forall a b. (Typeable a, Typeable b) => NewLVal a -> Pure b -> Either String (Pure b)
matchType = case eqT #a #b of
Nothing -> Left "types are not equal"
Just Refl -> {- in this scope the compiler knows that
a and b are the same type -}

Possible to generically remove function types from datatype, to allow deriveJSON?

I have several datatypes representing the state of an application. In various places in the datatype, I have embedded functions or monadic actions, eg.
data Foo = Foo Int (ActionM String)
data Bar = Bar Foo (Maybe Bar) (ActionM ())
I need to encode most of these datatypes as json so I can send it to the browser for display. Using deriveJSON (from the Aeson package) doesn't work because instances for ActionM can't be derived. However, I don't actually want those bits to be sent anyway. I currently have an approach which works but is basically copy-pasting the full set of datatypes and manually removing the embeded ActionM fields.
I (think I) need one of a couple of things. Either
a way to tell deriveJSON to just ignore fields that it can't figure out, and maybe parse them back into undefined. As far as I can tell this doesn't exist
a way to automatically generate a parallel set of datatypes with these fields removed. So I want to write something like
applyMagic Bar
and get back
data Foo' = Foo' Int
data Bar' = Bar' Foo' (Maybe Bar')
Is any of this possible, and how would I do it?
This is a simplistic solution, but couldn't you do something like
data Foo' = Foo' Int
type Foo = (ActionM String, Foo')
and simply obtain the second element of the tuple when you want to serialize?
Tuples are an instance of ComonadEnv, so you could also use functions like ask and extract.
Edit. Bar is a more complicated case because it is a recursive type. But it could be handled using the CofreeT comonad transformer:
import Data.Functor.Identity
import Data.Bifunctor (second)
import Control.Comonad -- from 'comonad'
import Control.Comonad.Hoist.Class
import Control.Comonad.Trans.Cofree -- from 'free'
-- Orphan ComonadHoist instance that will likely be added in future
-- versions of free
instance Functor f => ComonadHoist (CofreeT f) where
cohoist g = CofreeT . fmap (second (cohoist g)) . g . runCofreeT
type Bar = CofreeT Maybe ((,) (ActionM ())) Foo
type Bar' = Cofree Maybe Foo'
applyMagic :: Bar -> Bar'
applyMagic = cohoist (Identity . extract) . fmap extract
CofreeT Maybe ((,) (ActionM ())) Foo is a non-empty list of Foo values that have been annotated with ActionM () values.
Cofree Maybe Foo' is a non-empty list of Foo' values, without extra annotations (Cofree Maybe Foo is a synonym for CofreeT Maybe Identity Foo', where Identity works as the trivial comonad.).
To transform one into the other, applyMagic first uses fmap extract to transform all the Foos into Foo's, and then uses cohoist from ComonadHoist to remove the "annotation layer" underneath CofreeT.
In general, values with "extra context" can often be modeled with comonads.

Does exporting type constructors make a difference?

Let's say I have an internal data type, T a, that is used in the signature of exported functions:
module A (f, g) where
newtype T a = MkT { unT :: (Int, a) }
deriving (Functor, Show, Read) -- for internal use
f :: a -> IO (T a)
f a = fmap (\i -> T (i, a)) randomIO
g :: T a -> a
g = snd . unT
What is the effect of not exporting the type constructor T? Does it prevent consumers from meddling with values of type T a? In other words, is there a difference between the export list (f, g) and (f, g, T()) here?
Prevented
The first thing a consumer will see is that the type doesn't appear in Haddock documentation. In the documentation for f and g, the type Twill not be hyperlinked like an exported type. This may prevent a casual reader from discovering T's class instances.
More importantly, a consumer cannot doing anything with T at the type level. Anything that requires writing a type will be impossible. For instance, a consumer cannot write new class instances involving T, or include T in a type family. (I don't think there's a way around this...)
At the value level, however, the main limitation is that a consumer cannot write a type annotation including T:
> :t (f . read) :: Read b => String -> IO (A.T b)
<interactive>:1:39: Not in scope: type constructor or class `A.T'
Not prevented
The restriction on type signatures is not as significant a limitation as it appears. The compiler can still infer such a type:
> :t f . read
f . read :: Read b => String -> IO (A.T b)
Any value expression within the inferrable subset of Haskell may therefore be expressed regardless of the availability of the type constructor T. If, like me, you're addicted to ScopedTypeVariables and extensive annotations, you may be a little surprised by the definition of unT' below.
Furthermore, because typeclass instances have global scope, a consumer can use any available class functions without additional limitation. Depending on the classes involved, this may allow significant manipulation of values of the unexposed type. With classes like Functor, a consumer can also freely manipulate type parameters, because there's an available function of type T a -> T b.
In the example of T, deriving Show of course exposes the "internal" Int, and gives a consumer enough information to hackishly implement unT:
-- :: (Show a, Read a) => T a -> (Int, a)
unT' = (read . strip . show') `asTypeOf` (mkPair . g)
where
strip = reverse . drop 1 . reverse . drop 9
-- :: T a -> String
show' = show `asTypeOf` (mkString . g)
mkPair :: t -> (Int, t)
mkPair = undefined
mkString :: t -> String
mkString = undefined
> :t unT'
unT' :: (Show b, Read b) => A.T b -> (Int, b)
> x <- f "x"
> unT' x
(-29353, "x")
Implementing mkT' with the Read instance is left as an exercise.
Deriving something like Generic will completely explode any idea of containment, but you'd probably expect that.
Prevented?
In the corners of Haskell where type signatures are necessary or where asTypeOf-style tricks don't work, I guess not exporting the type constructor could actually prevent a consumer from doing something they could with the export list (f, g, T()).
Recommendation
Export all type constructors that are used in the type of any value you export. Here, go ahead and include T() in your export list. Leaving it out doesn't accomplish anything other than muddying the documentation. If you want to expose an purely abstract immutable type, use a newtype with a hidden constructor and no class instances.

Showing the type A -> A

data A = Num Int
| Fun (A -> A) String deriving Show
instance Show (Fun (A -> A) String) where
show (Fun f s) = s
I would like to have an attribute for a function A -> A to print it, therefore there is a String type parameter to Fun. When I load this into ghci, I get
/home/kmels/tmp/show-abs.hs:4:16:
Not in scope: type constructor or class `Fun'
I guess this could be achieved by adding a new data type
data FunWithAttribute = FA (A -> A) String
adding data A = Num Int | Fun FunWithAttribute and writing an instance Show FunWithAttribute. Is the additional data type avoidable?
Instances are defined for types as a whole, not individual constructors, which is why it complains about Fun not being a type.
I assume your overall goal is to have a Show instance for A, which can't be derived because functions can't (in general) have a Show instance. You have a couple options here:
Write your own Show instance outright:
That is, something like:
instance Show A where
show (Num n) = "Num " ++ show n
show (Fun _ s) = s
In many cases, this makes the most sense. But sometimes it's nicer to derive Show, especially on complex recursive types where only one case of many is not automatically Show-able.
Make A derivable:
You can only derive Show for types that contain types that themselves have Show instances. There's no instance for A -> A, so deriving doesn't work. But you can write one that uses a placeholder of some sort:
instance Show (A -> A) where
show _ = "(A -> A)"
Or even just an empty string, if you prefer.
Note that this requires the FlexibleInstances language extension; it's one of the most harmless and commonly used extensions, is supported by multiple Haskell implementations, and the restrictions it relaxes are (in my opinion) a bit silly to begin with, so there's little reason to avoid it.
An alternate approach would be to have a wrapper type, as you mention in the question. You could even make this more generic:
data ShowAs a = ShowAs a String
instance Show (ShowAs a) where
show (ShowAs _ s) = s
...and then use (ShowAs (A -> A)) in the Fun constructor. This makes it a bit awkward by forcing you to do extra pattern matching any time you want to use the wrapped type, but it gives you lots of flexibility to "tag" stuff with how it should be displayed, e.g. showId = id `ShowAs` "id" or suchlike.
Perhaps I'm not following what you are asking for. But the above code could be written like this in order to compile:
data A = Num Int
| Fun (A -> A) String
instance Show A where
show (Fun f s) = s
show (Num i) = show i
Some explanation
It looked like you were trying to write a show instance for a constructor (Fun). Class instances are written for the entire data type (there might be exceptions, dunno). So you need to write one show matching on each constructor as part of the instance. Num and Fun are each constructors of the data type A.
Also, deriving can't be used unless each parameter of each constructor is, in turn, member of, in this case, Show. Now, your example is a bit special since it wants to Show (A -> A). How to show a function is somewhat explained in the other responses, although I don't think there is an exhaustive way. The other examples really just "show" the type or some place holder.
A Show instance (or any class instance) needs to be defined for a data type, not for a type constructor. That is, you need simply
instance Show A where
Apparently, you're trying to get this instance with the deriving, but that doesn't work because Haskell doesn't know how to show A->A. Now it seems you don't even want to show that function, but deriving Show instances always show all available information, so you can't use that.
The obvious, and best, solution to your problem is worldsayshi's: don't use deriving at all, but define a proper instance yourself. Alternatively, you can define a pseudo-instance for A->A and then use deriving:
{-# LANGUAGE FlexibleInstances #-}
data A = Num Int | Fun (A->A) String deriving(Show)
instance Show (A->A) where show _ = ""
This works like
Prelude> Fun (const $ Num 3) "bla"
Fun "bla"

Resources