Type class polymorphism with overloaded numeric and string literals - haskell

I'm trying to write some EDSL for assigning values to keys. So I have the following data type for value:
data Value = B Bool | I Int
I want to have unified way to convert different values to objects of type Value. So I've created the following type class:
class ToValue a where toValue :: a -> Value
instance ToValue Bool where toValue = B
instance ToValue Int where toValue = I
Unfortunately, this code doesn't compile:
foo :: [Value]
foo = [toValue True, toValue 3]
I understand the reason why. But this makes me sad. I don't really understand how to solve this problem... And things become more difficult if I have -XOverloadedStrings enabled and I want to add T Text constructor to my Value type.
My final goal is to have ability to write something like this:
foo :: [(Text, Value)]
foo = [ "key1" !!! True
, "key2" !!! 42
, "key3" !!! "foo"
, "key4" !!! [5, 7, 10]
]
I understand that I can always wrap manually every value into corresponding constuctor but I'd prefer to avoid that (since in my real life constructors are longer than one letter and code doesn't really decrease in noise with constructors).
What can I do to achieve the closest possible implementation? I would like to avoid unsafe Num instance for Value if possible...

Use ExtendedDefaultRules. (It is enabled by default in GHCi, and the pragma enables it in GHC.)
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ExtendedDefaultRules #-}
{-# LANGUAGE OverloadedStrings #-}
default (Int, String)
class Value a where
toValue :: a -> String
instance Value Int where
toValue = show
instance Value String where
toValue = id
main = do
print (toValue 3) -- would otherwise be ambiguous
print (toValue "x")
Old answer
If I understand correctly, the goal here is to keep the syntax uniform while properly specializing literals. One way is to use Template Haskell, so foo might look like
foo = [$(toValue [|True|]), $(toValue [|3|])]
or
foo = [ [toValue| True |], [toValue| 3 |] ]
The latter is less dollar-noisy, but implementing a custom quote requires an expression parser and template-haskell doesn't provide one.

Related

Haskell not using the more specific instance of a typeclass

I've been having trouble the past few days figuring out whether something I'm trying to do is actually feasible in Haskell.
Here is some context:
I am trying to code a little markup language (akin to ReST) where the syntax already enables custom extensions through directives.
For users to implement new directives, they should be able to add new semantic constructs inside the document datatype. For exemple if one wants to add a directive for displaying math, they might want to have a MathBlock String constructor inside the ast.
Obviously data types are not extensible, and a solution where there is a generic constructor DirectiveBlock String containing the name of the directive (here, "math") is undesirable as we would like to have in our ast only well-formed constructs (so only directives with well-formed arguments).
Using type families, I prototyped something like:
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
-- Arguments for custom directives.
data family Args :: * -> *
data DocumentBlock
= Paragraph String
| forall a. Block (Args a)
Sure enough, if someone wishes to define a new directive for math display, they can do it as such:
data Math
-- The expected arguments for the math directive.
data instance Args Math = MathArgs String
doc :: [DocumentBlock]
doc =
[ Paragraph "some text"
, Block (MathArgs "x_{n+1} = x_{n} + 3")
]
So far so good, we can only construct documents where directive blocks receive the correct arguments.
The problem arises when one user wants to convert the internal representation of a document to some custom output, say, String.
The user needs to provide a default output for all directives, since there will be many and some of them cannot be converted to the target.
Furthermore, the user may wish to provide a more specific output for some directives:
class StringWriter a where
write :: Args a -> String
-- User defined generic conversion for all directives.
instance StringWriter a where
write _ = "Directive"
-- Custom way of showing the math directive.
instance StringWriter Math where
write (MathArgs raw) = "Math(" ++ raw ++ ")"
-- Then to display a DocumentBlock
writeBlock :: DocumentBlock -> String
writeBlock (Paragraph t) = "Paragraph(" ++ t ++ ")"
writeBlock (Block args) = write args
main :: IO ()
main = putStrLn $ writeBlock (Block (MathArgs "a + b"))
With this example, the output is Block and not Math(a+b), so the generic instance for StringWriter is always chosen. Even when playing with {-# OVERLAPPABLE #-}, nothing succeeds.
Is the kind of behavior I'm describing possible at all in Haskell?
When trying to include a generic Writer inside the Block definition, it also fails to compile.
-- ...
class Writer a o where
write :: Args a -> o
data DocumentBlock
= Paragraph String
| forall a o. Writer a o => Block (Args a)
instance {-# OVERLAPPABLE #-} Writer a String where
write _ = "Directive"
instance {-# OVERLAPS #-} Writer Math String where
write (MathArgs raw) = "Math(" ++ raw ++ ")"
-- ...
Your code does not compile, since Block something has type DocumentBlock, while write expects an Args a argument, and the two types are different.
Did you mean writeBlock instead? I'll assume so.
What you might want to try is to add a constraint in your existential type, e.g.:
data DocumentBlock
= Paragraph String
| forall a. StringWriter a => Block (Args a)
-- ^^^^^^^^^^^^^^ --
This has the following effect. Operationally, every time Block something is used, the instance is remembered (a pointer is implicitly stored along the Args a value). That will be a pointer to the catch-all instance, or to the specific one, whichever is the best fit.
When the constructor is then pattern-matched later on, the instance can then be used. Full working code:
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
-- Arguments for custom directives.
data family Args :: * -> *
data DocumentBlock
= Paragraph String
| forall a. StringWriter a => Block (Args a)
data Math
-- The expected arguments for the math directive.
data instance Args Math = MathArgs String
doc :: [DocumentBlock]
doc =
[ Paragraph "some text"
, Block (MathArgs "x_{n+1} = x_{n} + 3")
]
class StringWriter a where
write :: Args a -> String
-- User defined generic conversion for all directives.
instance {-# OVERLAPPABLE #-} StringWriter a where
write _ = "Directive"
-- Custom way of showing the math directive.
instance StringWriter Math where
write (MathArgs raw) = "Math(" ++ raw ++ ")"
-- Then to display a DocumentBlock
writeBlock :: DocumentBlock -> String
writeBlock (Paragraph t) = "Paragraph(" ++ t ++ ")"
writeBlock (Block args) = write args
main :: IO ()
main = putStrLn $ writeBlock (Block (MathArgs "a + b"))
This prints Math(a + b).
A final note: for this to work it is crucial that all the relevant instances are in scope when Block is used. Otherwise, GHC might choose the wrong instance, causing some unintended output. This is the main limitation, making overlapping instances a bit fragile in general.
As long as there are no orphan instances, this should work.
Also note that, if using other existential types, a user can (intentionally or accidentally) cause GHC to pick the wrong instance anyway. For instance, if we use
data SomeArgs = forall a. SomeArgs (Args a)
toGenericInstance :: DocumentBlock -> DocumentBlock
toGenericInstance (Block a) = case SomeArgs a of
SomeArgs a' -> Block a' -- this will always pick the generic instance
toGenericInstance db = db
then, writeBlock (toGenericInstance (Block (MathArgs "a + b")))
will produce Directive instead.

Safe Record field query

Is there a clean way to avoid the following boilerplate:
Given a Record data type definition....
data Value = A{ name::String } | B{ name::String } | C{}
write a function that safely returns name
getName :: Value -> Maybe String
getName A{ name=x } = Just x
getName B{ name=x } = Just x
getName C{} = Nothing
I know you can do this with Template Haskell, I am looking for a cleaner soln than that, perhaps a GHC extension or something else I've overlooked.
lens's Template Haskell helpers do the right thing when they encounter partial record fields.
{-# LANGUAGE TemplateHaskell #-}
import Control.Applicative
import Control.Lens
data T = A { _name :: String }
| B { _name :: String }
| C
makeLenses ''T
This'll generate a Traversal' called name that selects the String inside the A and B constructors and does nothing in the C case.
ghci> :i name
name :: Traversal' T String -- Defined at test.hs:11:1
So we can use the ^? operator (which is a flipped synonym for preview) from Control.Lens.Fold to pull out Maybe the name.
getName :: T -> Maybe String
getName = (^? name)
You can also make Prism's for the constructors of your datatype, and choose the first one of those which matches using <|>. This version is useful when the fields of your constructors have different names, but you do have to remember to update your extractor function when you add constructors.
makePrisms ''T
getName' :: T -> Maybe String
getName' t = t^?_A <|> t^?_B
lens is pretty useful!
Why don't you use a GADT? I do not know if you are interested in using only records. But, I fell that GADTs provide a clean solution to your problem, since you can restrict what constructors are valid by refining types.
{-# LANGUAGE GADTs #-}
module Teste where
data Value a where
A :: String -> Value String
B :: String -> Value String
C :: Value ()
name :: Value String -> String
name (A s) = s
name (B s) = s
Notice that both A and B produce Value String values while C produces Value (). When you define function
name :: Value String -> String
it specifically says that you can only pass a value that has a string in it. So, you can only pattern match on A or B values. This is useful to avoid the need of Maybe in code.

How to avoid default return value when accessing a non-existent field with lenses?

I love Lens library and I love how it works, but sometimes it introduces so many problems, that I regret I ever started using it. Lets look at this simple example:
{-# LANGUAGE TemplateHaskell #-}
import Control.Lens
data Data = A { _x :: String, _y :: String }
| B { _x :: String }
makeLenses ''Data
main = do
let b = B "x"
print $ view y b
it outputs:
""
And now imagine - we've got a datatype and we refactor it - by changing some names. Instead of getting error (in runtime, like with normal accessors) that this name does not longer apply to particular data constructor, lenses use mempty from Monoid to create default object, so we get strange results instead of error. Debugging something like this is almost impossible.
Is there any way to fix this behaviour? I know there are some special operators to get the behaviour I want, but all "normal" looking functions from lenses are just horrible. Should I just override them with my custom module or is there any nicer method?
As a sidenote: I want to be able to read and set the arguments using lens syntax, but just remove the behaviour of automatic result creating when field is missing.
It sounds like you just want to recover the exception behavior. I vaguely recall that this is how view once worked. If so, I expect a reasonable choice was made with the change.
Normally I end up working with (^?) in the cases you are talking about:
> b ^? y
Nothing
If you want the exception behavior you can use ^?!
> b ^?! y
"*** Exception: (^?!): empty Fold
I prefer to use ^? to avoid partial functions and exceptions, similar to how it is commonly advised to stay away from head, last, !! and other partial functions.
Yes, I too have found it a bit odd that view works for Traversals by concatenating the targets. I think this is because of the instance Monoid m => Applicative (Const m). You can write your own view equivalent that doesn't have this behaviour by writing your own Const equivalent that doesn't have this instance.
Perhaps one workaround would be to provide a type signature for y, so know know exactly what it is. If you had this then your "pathological" use of view wouldn't compile.
data Data = A { _x :: String, _y' :: String }
| B { _x :: String }
makeLenses ''Data
y :: Lens' Data String
y = y'
You can do this by defining your own view1 operator. It doesn't exist in the lens package, but it's easy to define locally.
{-# LANGUAGE TemplateHaskell #-}
import Control.Lens
data Data = A { _x :: String, _y :: String }
| B { _x :: String }
makeLenses ''Data
newtype Get a b = Get { unGet :: a }
instance Functor (Get a) where
fmap _ (Get x) = Get x
view1 :: LensLike' (Get a) s a -> s -> a
view1 l = unGet . l Get
works :: Data -> String
works = view1 x
-- fails :: Data -> String
-- fails = view1 y
-- Bug.hs:23:15:
-- No instance for (Control.Applicative.Applicative (Get String))
-- arising from a use of ‘y’

How to handle functions of a multi-parameter typeclass, who not need every type of the typeclass?

I've defined a typeclass similar to an interface with a bunch of functions required for my program. Sadly, it needs multiple polymorphic types, but not every function of this multi-parameter typeclass needs every type. GHC haunts me with undeduceable types and i can't get the code running.
A reduced example:
{-# LANGUAGE MultiParamTypeClasses #-}
class Foo a b where
-- ...
bar :: a -> ()
baz :: Foo a b => a -> ()
baz = bar
GHC says
Possible fix: add a type signature that fixes these type variable(s)
How can I do this for b? Especially when I want to keep b polymorphic. Only an instance of Foo should define what this type is.
This is impossible.
The underlying problem is that a multiparameter type class depends on every type parameter. If a particular definition in the class doesn't use every type parameter, the compiler will never be able to know what instance you mean, and you'll never even be able to specify it. Consider the following example:
class Foo a b where
bar :: String -> IO a
instance Foo Int Char where
bar x = return $ read x
instance Foo Int () where
bar x = read <$> readFile x
Those two instances do entirely different things with their parameter. The only way the compiler has to select one of those instances is matching both type parameters. But there's no way to specify what the type parameter is. The class is just plain broken. There's no way to ever call the bar function, because you can never provide enough information for the compiler to resolve the class instance to use.
So why is the class definition not rejected by the compiler? Because you can sometimes make it work, with the FunctionalDependencies extension.
If a class has multiple parameters, but they're related, that information can sometimes be added to the definition of the class in a way that allows a class member to not use every type variable in the class's definition.
class Foo a b | a -> b where
bar :: String -> IO a
With that definition (which requires the FunctionalDependencies extension), you are telling the compiler that for any particular choice of a, there is only one valid choice of b. Attempting to even define both of the above instances would be a compile error.
Given that, the compiler knows that it can select the instance of Foo to use based only on the type a. In that case, bar can be called.
Splitting it in smaller typeclasses might be sufficient.
{-# LANGUAGE MultiParamTypeClasses #-}
class Fo a => Foo a b where
-- ...
foo :: a -> b -> ()
class Fo a where
bar :: a -> ()
baz :: Foo a b => a -> ()
baz = bar
Assuming you really want to use more than one instance for a given a (and so cannot use functional dependencies as others mentioned), one possibility which may or may not be right for you is to use a newtype tagged with a "phantom" type used only to guide type selection. This compiles:
{-# LANGUAGE MultiParamTypeClasses #-}
newtype Tagged t a = Tagged { unTagged :: a } -- Also defined in the tagged package
-- on Hackage
class Foo a b where
bar :: Tagged b a -> ()
baz :: Foo a b => Tagged b a -> ()
baz = bar
Then you will be able to wrap your values in such a way that you can give an explicit type annotation to select the right instance.
Another way of refactoring multi-parameter type classes when they get awkward is to use the TypeFamilies extension. Like FunctionalDependencies, this works well when you can reframe your class as having only a single parameter (or at least, fewer parameter), with the other types that are different from instance to instance being computed from the actual class parameters.
Generally I've found whenever I thought I needed a multi-parameter type class, the parameters almost always varied together rather than varying independently. In this situation it's much easier to pick one as "primary" and use some system for determining the others from it. Functional dependencies can do this as well as type families, but many find type families a lot easier to understand.
Here's an example:
{-# LANGUAGE TypeFamilies, FlexibleInstances #-}
class Glue a where
type Glued a
glue :: a -> a -> Glued a
instance Glue Char where
type Glued Char = String
glue x y = [x, y]
instance Glue String where
type Glued String = String
glue x y = x ++ y
glueBothWays :: Glue a => a -> a -> (Glued a, Glued a)
glueBothWays x y = (glue x y, glue y x)
The above declares a class Glue of types that can be glued together with the glue operation, and that have a corresponding type which is the result of the "gluing".
I then declared a couple of instances; Glued Char is String, Glued String is also just String.
Finally I wrote a function to show how you use Glued when you're being polymorphic over the instance of Glue you're using; basically you "call" Glued as a function in your type signatures; this means glueBothWays doesn't "know" what type Glued a is, but it knows how it corresponds to a. You can even use Glued Char as a type, if you know you're gluing Chars but don't want to hard-code the assumption that Glued Char = String.

How can I use restricted constraints with GADTs?

I have the following code, and I would like this to fail type checking:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
import Control.Lens
data GADT e a where
One :: Greet e => String -> GADT e String
Two :: Increment e => Int -> GADT e Int
class Greet a where
_Greet :: Prism' a String
class Increment a where
_Increment :: Prism' a Int
instance Greet (Either String Int) where
_Greet = _Left
instance Increment (Either String Int) where
_Increment = _Right
run :: GADT e a -> Either String Int
run = go
where
go (One x) = review _Greet x
go (Two x) = review _Greet "Hello"
The idea is that each entry in the GADT has an associated error, which I'm modelling with a Prism into some larger structure. When I "interpret" this GADT, I provide a concrete type for e that has instances for all of these Prisms. However, for each individual case, I don't want to be able to use instances that weren't declared in the constructor's associated context.
The above code should be an error, because when I pattern match on Two I should learn that I can only use Increment e, but I'm using Greet. I can see why this works - Either String Int has an instance for Greet, so everything checks out.
I'm not sure what the best way to fix this is. Maybe I can use entailment from Data.Constraint, or perhaps there's a trick with higher rank types.
Any ideas?
The problem is you're fixing the final result type, so the instance exists and the type checker can find it.
Try something like:
run :: GADT e a -> e
Now the result type can't pick the instance for review and parametricity enforces your invariant.

Resources