StateT with Q monad from template haskell - haskell

I would like to create a function that takes some declarations of type Dec (which I get from [d| ... |]) and modify them. Modifications will depend on previous declarations so I would like to be able to store them in map hidden in State monad - mainly I create records and class instances and add to them fields from previous records. (This way I want to mimic OOP but this is probably not relevant for my question). I would like to splice results of my computations to code after I processed (and changed) all declarations.
I tried composing StatT with Q every possible way but I can't get it right.
Edit
My idea was to create functions collecting classes declarations (I am aware that Haskell is not object oriented language, I read some papers about how you can encode OOP in Haskell and I try to implement it with Template Haskell as small assignment).
So I would like to be able to write something like this:
declare [d| class A a where
attr1 :: a -> Int
attr2 :: a -> Int |]
declareInherit [d| class B b where
attr3 :: b -> Int |] ''A
This is encoding of (for example c++ code)
struct A{
int attr1;
int attr2;
}
struct B : A {
int attr3;
}
And I would like to generate two records with template haskell:
data A_data = A_data { attr1' :: Int, attr2' :: Int}
data B_data = B_data { attr1'' :: Int, attr2'' :: Int, attr3'' :: Int}
and instances of classes:
instance A A_data where
attr1 = attr1'
attr2 = attr2'
instance A B_data where
attr1 = attr1''
attr2 = attr2''
instance B B_data where
attr3 = attr3''
This is how my encoding of OO works, but I would like to be able to generate it automatically, not write it by hand.
I had a problem with interacting with DecsQ in declare function, probably I would like it to exist in something like this:
data Env = Env {classes :: Map.Map Name Dec }
type QS a = (StateT Env Q) a
I also has problem how to run computation in QS.

A problem with Template Haskell is that its API is not as polished as in most of other Haskell libraries. The Q monad is overloaded with problems: it reifies, it renders, it manages the state of local names. But it is never a good idea to interleave problem domains, since it's been proven that human beings can only think about one thing at a time (in other words, we're "single core"). This means that mixing problems together is not scalable. That is why it is hard to reason about Q already, and you want to add yet another problem on top of it: your state. Bad idea.
As well as any other problem you should approach this with separation of concerns. I.e., you should extract smaller problem domains from your main one and work with each of them in isolation. Concerning Template Haskell there are several evident domains: reification of existing ASTs, their analysis and rendering of new ASTs. For communication between those domains you may also need some "lingua franca" data model. Kinda reminds of something, doesn't it? Yep, it's MVC.
There are certain properties of the extracted domains, which you can then exploit to your benefits: you only need to remain in the Q monad for reification, the rendering and analysis can be done in the pure environment, granting you with all of its benefits. You can safely purify quasi-quotes using unsafePerformIO . runQ.
For real-life examples I can refer you to some of my projects, in which I apply this approach:
https://github.com/nikita-volkov/type-structure/blob/404017df89d3432481ed118776713cbd660ba220/src/TypeStructure/TH.hs
https://github.com/nikita-volkov/graph-db/blob/ba6ca0343ce73011b1c801d74aa3e17e0250d8a4/library/GraphDB/Macros.hs

At least within one file, you can pass state from one DecsQ splice to the one lower down in the file by storing it in:
{-# NOINLINE env #-}
env :: IORef Env
env = unsafePerformIO (newIORef (Env mempty))
and then do things like runIO (readIORef env) :: Q Env.

Related

How to modify parts of a State in Haskell

I have a number of operations which modify a System. System is defined like this:
data System = Sys {
sysId :: Int,
sysRand :: StdGen,
sysProcesses :: ProcessDb,
sysItems :: ItemDb
}
with e.g.
type ProcessDb = M.Map Int Process
But I also have some functions, which do not need access to the full System, but have types like this:
foo' :: (Process, ItemDb) -> ((Process, ItemDb),[Event])
Currently I gave them types like
foo: System -> (System, [Event])
But this is a needlessly broad interface. To use the narrow interface above in conjuntion with System I would have to extract a single Process and the ItemDb from System, run foo' and then modify System with the results.
This is quite some unwrapping and wrapping and results in more lines of code than just passing system as a whole and let foo extract whatever it needs. In the latter case, the wrapping and unwrapping is mingled with the actual foo' operation and I have the feeling that these two aspects should be separated.
I suppose I need some kind of lifting operation which turns a narrow foo' into a foo. I suppose I could write this, but I would have to write such a lifter for every signature of the narrow functions, resulting is lots of different lifters.
is there an idiom how to solve such problems?
is it worth bothering?
One common solution is to use a class, possibly created by the Template Haskell magic of Control.Lens.TH.makeClassy. The gist is that you pass in the whole System, but you don't let the function know that that's what you're giving it. All it's allowed to know is that what you're giving it offers methods for getting and/or modifying the pieces it's supposed to handle.
I ended up writing a function which work on any State and which requires a "Lens" which captures the specfic transformation from the bigger State to the smaller State and back
focus :: (Lens s' s) -> State s' a -> State s a
focus lens ms'= do
s <- get
let (s', set) = lens s
(a, s'') = runState ms' s'
put (set s'')
return a
It allows me to write things like
run :: ExitP -> State SimState Log
...
do
evqs' <-focus onSys $ step (t,evt)
...
Where step operates on the "smaller" state
step :: Timed Event -> State Sys.System [EventQu]
Here onSys is a "Lens" and it works like this:
onSys :: Lens Sys.System SimState
onSys (Sis e s) = (s, Sis e)
where
data SimState = Sis {
events :: EventQu,
sisSys :: Sys.System
I suppose the existing Lens libraries follow a similar approach, but do much more magic, like creating lenses automatically. I did shy away from lenses. Instead I was pleased to realise that all it takes was a few lines of codes to get what I need.

Moving from static configuration to dynamic configuration

I am working on a haskell project where the settings are currently in a file called Setting.hs, so they are checked during compile time and can be accessed globally.
However, since that is a bit too static, I was considering to read the configuration during runtime. The codebase is huge and it seems it would be considerable effort to pass the setting e.g. as an argument through the whole program flow, since they may be arbitrarily accessed from anywhere.
Are there any design patterns, libraries or even ghc extensions that can help here without refactoring the whole code?
Thanks for the hints! I came up with a minimal example which shows how I will go about it with the reflection package:
{-# LANGUAGE Rank2Types, FlexibleContexts, UndecidableInstances #-}
import Data.Reflection
data GlobalConfig = MkGlobalConfig {
getVal1 :: Int
, getVal2 :: Double
, getVal3 :: String
}
main :: IO ()
main = do
let config = MkGlobalConfig 1 2.0 "test"
-- initialize the program flow via 'give'
print $ give config (doSomething 2)
-- this works too, the type is properly inferred
print $ give config (3 + 3)
-- and this as well
print $ give config (addInt 7 3)
-- We need the Given constraint, because we call 'somethingElse', which finally
-- calls 'given' to retrieve the configuration. So it has to be propagated up
-- the program flow.
doSomething :: (Given GlobalConfig) => Int -> Int
doSomething = somethingElse "abc"
-- since we call 'given' inside the function to retrieve the configuration,
-- we need the Given constraint
somethingElse :: (Given GlobalConfig) => String -> Int -> Int
somethingElse str x
| str == "something" = x + getVal1 given
| getVal3 given == "test" = 0 + getVal1 given
| otherwise = round (fromIntegral x * getVal2 given)
-- no need for Given constraint here, since this does not use 'given'
-- or any other functions that would
addInt :: Int -> Int -> Int
addInt = (+)
The Given class is a bit easier to work with and perfectly suitable for a global configuration model. All functions that do not make use of given (which gets the value) don't seem to need the class constraint. That means I only have to change functions that actually access the global configuration.
That's what I was looking for.
What you are asking, if it was possible would break referential transparency, at least for pure function ( a pure function result can depend on some global variables but not on a config file couldn't it ) ?
Usually people avoid that type of situation by passing implicitly the configuration as data via a Monad. Alternatively (if you are happy to refactor your code a bit) you can use the implicit parameter extenson, which in theory has been made to solve that type of problem but in practice doesn't really work.
However, if you really need, you can use unsafePerformIO and ioRef to have a top level mutable state which is dirty and frowned upton. You need a top level mutable state, because you need to be able to modify "mutate" your initial config when you are loading it.
Then you get things like that :
myGlobalVar :: IORef Int
{-# NOINLINE myGlobalVar #-}
myGlobalVar = unsafePerformIO (newIORef 17)

Why doesn't GHC Haskell support overloaded record parameter names?

What I am talking about is that it is not possible to define:
data A = A {name :: String}
data B = B {name :: String}
I know that the GHC just desugars this to plain functions and the idiomatic way to solve this would be:
data A = A {aName :: String}
data B = B {bName :: String}
class Name a where
name :: a -> String
instance Name A where
name = aName
instance Name B where
name = bName
After having written this out I don't like it that much ... couldn't this typeclassing be part of the desugaring process?
The thought came to me when I was writing some Aeson JSON parsing. Where it would have been too easy to just derive the FromJSON instances for every data type I had to write everything out by hand (currently >1k lines and counting).
Having names like name or simply value in a data record is not that uncommon.
http://www.haskell.org/haskellwiki/Performance/Overloading mentions that function overloading introduces some runtime overhead. But I actually don't see why the compiler wouldn't be able to resolve this at compile time and give them different names internally.
This SO question from 2012 more or less states historical reasons and points to a mail thread from 2006. Has anything changed recently?
Even if there would be some runtime overhead most people wouldn't mind cause most code hardly is performance critical.
Is there some hidden language extension that actually allows this? Again I am not sure ... but I think Idris actually does this?
Many, mostly minor reasons. One is the problem raised by a better answer, overloading just on the first argument is insufficient to handle all the useful cases.
You could "desugar"
data A { name :: String }
data B { name :: Text }
into
class Has'name a b | a -> b where
name :: a -> b
data A { aName :: String }
instance Has'name A String where
name :: aName
data B { bName :: Text }
instance Has'name B Text where
name :: bName
but that would require GHC extensions (Functional Dependencies) that haven't made it into the standard, yet. It would preclude using just 'name' for record creation, updates, and pattern matching (view patterns might help there), since 'name' isn't "just" a function in those cases. You can probably pull off something very similar with template Haskell.
Using the record syntax
data A { name :: String }
implicitly defines a function
name :: A -> String
If define both A and B with a { name :: String }, we have conflicting type definitions for name:
name :: A -> String
name :: B -> String
It's not clear how your proposed implicit type classes would work because if we define two types
data A { name :: String }
data B { name :: Text }
then we have just shifted the problem to conflicting type class definitions:
class Has'name a where
name :: a -> String
class Has'name a where
name :: a -> Text
In principle this could be resolved one way or another, but this is just one of several tricky conflicting desirable properties for records. When Haskell was defined, it was decided that it was better to have simple if limited support rather than to try to design something more ambitious and complicated. Several improvements to records have been discussed at various times and there are perennial discussions, e.g. this Haskell Cafe thread. Perhaps something will be worked out for Haskell Prime.
The best way I found, is to use a preprocessor to solve this definitely rather stupid problem.
Haskell and GHC make this easy, because the whole Haskell parser is available as a normal library. You could just parse all the files, do that renaming scheme (e.g. « data A { name :: String } » and « let a = A "Betty" in name a » into « data A { a_Name :: String } » and « let a = A "Betty" in aName a ») depending on the type of data the name function is applied to, using the type resolver, and write them out for compilation.
But honestly, that should be integrated into GHC. You’re right: It’s silly that this isn’t included.

Transparently implementing a particular form of dynamic typing

The basic idea is that I have a range of functions that work on any types from a particular class, but at runtime the program is supposed to read a configuration file and extract an element of one of the types in the class.
For instance, I have a 'Coefficient' class, various instances of it, and functions of various types that are polymorphic over types of that class; at runtime one particular type of that class is to be determined, and passed around.
I'm unsure how to properly address this; I tried making up 'compound' types, doing something like:
data CompoundCoeff = CompoundInt Int | CompoundDouble Double | ...
where Int, Double, ... are instances of the class 'Coefficient'.
However, it started to become a big effort to adapt all the functions involved in the code to work with these compound types (and it's not a nice solution either, really). It would be OK if all functions had the same, easy type, e.g.
Coefficient a => a -> (stuff not involving a anymore)
but that's unfortunately not the case.
Another issue I ran into, is that I'm using type families, and have something like
class (Monoid (ColourData c), Coordinate (InputData c)) => ColourScheme c where
type ColourData c :: *
type InputData c :: *
colouriseData :: c -> (ColourData c) -> AlphaColour Double
processInput :: c -> InputData c -> ColourData c
This doesn't go through cleanly if I have to use some sort of compound ColourData datatype, like the previous one; in particular I can no longer guarantee that the data stream gives a consistent type (and not just different 'subtypes' of a compound type), and would (among other things) have to make up a bogus Monoid instance if I did make up a compound ColourData type.
I've also looked into Data.Dynamic, but again I can't see how it would properly address the issues; the exact same problems seem to appear (well, slightly worse even, given that there is only one 'generic' Dynamic type as I understand it).
Question: How can I implement dynamic datatypes subordinate to particular classes, without having to rewrite all the functions involving those data types? It would be best if I didn't have to sacrifice any type safety, but I'm not too optimistic.
The program is supposed to read a configuration file at runtime, and all the requisite functions, polymorphic over the relevant class, are to be applied.
The traditional way to provide an object that guarantees that it is an instance of typeclass Foo, but makes no additional guarantees, is like so:
{-# LANGUAGE ExistentialTypes #-}
data SomeFoo = forall a . Foo a => SomeFoo a
instance Foo SomeFoo where
-- all operations just unwrap the SomeFoo straightforwardly
or, with GADTs, which might be more readable...
data SomeFoo where
SomeFoo :: Foo a => a -> SomeFoo
One proposal would be to write a single top-level function that does all the finishing touches once you've chosen a type:
topLevel :: SomeTypeClass a => a -> IO ()
Your program can then be written something like this:
main = do
config <- readConfig
case config of
UseDouble n -> topLevel n
UseSymbolic x -> topLevel x
UseWidgetFrobnosticator wf -> topLevel wf

How to define a class that allows uniform access to different records in Haskell?

I have two records that both have a field I want to extract for display. How do I arrange things so they can be manipulated with the same functions? Since they have different fields (in this case firstName and buildingName) that are their name fields, they each need some "adapter" code to map firstName to name. Here is what I have so far:
class Nameable a where
name :: a -> String
data Human = Human {
firstName :: String
}
data Building = Building {
buildingName :: String
}
instance Nameable Human where
name x = firstName x
instance Nameable Building where
-- I think the x is redundant here, i.e the following should work:
-- name = buildingName
name x = buildingName x
main :: IO ()
main = do
putStr $ show (map name items)
where
items :: (Nameable a) => [a]
items = [ Human{firstName = "Don"}
-- Ideally I want the next line in the array too, but that gives an
-- obvious type error at the moment.
--, Building{buildingName = "Empire State"}
]
This does not compile:
TypeTest.hs:23:14:
Couldn't match expected type `a' against inferred type `Human'
`a' is a rigid type variable bound by
the type signature for `items' at TypeTest.hs:22:23
In the expression: Human {firstName = "Don"}
In the expression: [Human {firstName = "Don"}]
In the definition of `items': items = [Human {firstName = "Don"}]
I would have expected the instance Nameable Human section would make this work. Can someone explain what I am doing wrong, and for bonus points what "concept" I am trying to get working, since I'm having trouble knowing what to search for.
This question feels similar, but I couldn't figure out the connection with my problem.
Consider the type of items:
items :: (Nameable a) => [a]
It's saying that for any Nameable type, items will give me a list of that type. It does not say that items is a list that may contain different Nameable types, as you might think. You want something like items :: [exists a. Nameable a => a], except that you'll need to introduce a wrapper type and use forall instead. (See: Existential type)
{-# LANGUAGE ExistentialQuantification #-}
data SomeNameable = forall a. Nameable a => SomeNameable a
[...]
items :: [SomeNameable]
items = [ SomeNameable $ Human {firstName = "Don"},
SomeNameable $ Building {buildingName = "Empire State"} ]
The quantifier in the data constructor of SomeNameable basically allows it to forget everything about exactly which a is used, except that it is Nameable. Therefore, you will only be allowed to use functions from the Nameable class on the elements.
To make this nicer to use, you can make an instance for the wrapper:
instance Nameable (SomeNameable a) where
name (SomeNameable x) = name x
Now you can use it like this:
Main> map name items
["Don", "Empire State"]
Everybody is reaching for either existential quantification or algebraic data types. But these are both overkill (well depending on your needs, ADTs might not be).
The first thing to note is that Haskell has no downcasting. That is, if you use the following existential:
data SomeNameable = forall a. Nameable a => SomeNameable a
then when you create an object
foo :: SomeNameable
foo = SomeNameable $ Human { firstName = "John" }
the information about which concrete type the object was made with (here Human) is forever lost. The only things we know are: it is some type a, and there is a Nameable a instance.
What is it possible to do with such a pair? Well, you can get the name of the a you have, and... that's it. That's all there is to it. In fact, there is an isomorphism. I will make a new data type so you can see how this isomorphism arises in cases when all your concrete objects have more structure than the class.
data ProtoNameable = ProtoNameable {
-- one field for each typeclass method
protoName :: String
}
instance Nameable ProtoNameable where
name = protoName
toProto :: SomeNameable -> ProtoNameable
toProto (SomeNameable x) = ProtoNameable { protoName = name x }
fromProto :: ProtoNameable -> SomeNameable
fromProto = SomeNameable
As we can see, this fancy existential type SomeNameable has the same structure and information as ProtoNameable, which is isomorphic to String, so when you are using this lofty concept SomeNameable, you're really just saying String in a convoluted way. So why not just say String?
Your items definition has exactly the same information as this definition:
items = [ "Don", "Empire State" ]
I should add a few notes about this "protoization": it is only as straightforward as this when the typeclass you are existentially quantifying over has a certain structure: namely when it looks like an OO class.
class Foo a where
method1 :: ... -> a -> ...
method2 :: ... -> a -> ...
...
That is, each method only uses a once as an argument. If you have something like Num
class Num a where
(+) :: a -> a -> a
...
which uses a in multiple argument positions, or as a result, then eliminating the existential is not as easy, but still possible. However my recommendation to do this changes from a frustration to a subtle context-dependent choice, because of the complexity and distant relationship of the two representations. However, every time I have seen existentials used in practice it is with the Foo kind of tyepclass, where it only adds needless complexity, so I quite emphatically consider it an antipattern. In most of these cases I recommend eliminating the entire class from your codebase and exclusively using the protoized type (after you give it a good name).
Also, if you do need to downcast, then existentials aren't your man. You can either use an algebraic data type, as others people have answered, or you can use Data.Dynamic (which is basically an existential over Typeable. But don't do that; a Haskell programmer resorting to Dynamic is ungentlemanlike. An ADT is the way to go, where you characterize all the possible types it could be in one place (which is necessary so that the functions that do the "downcasting" know that they handle all possible cases).
I like #hammar's answer, and you should also check out this article which provides another example.
But, you might want to think differently about your types. The boxing of Nameable into the SomeNameable data type usually makes me start thinking about whether a union type for the specific case is meaningful.
data Entity = H Human | B Building
instance Nameable Entity where ...
items = [H (Human "Don"), B (Building "Town Hall")]
I'm not sure why you want to use the same function for
getting the name of a Human and the name of a Building.
If their names are used in fundamentally different ways,
except maybe for simple things like printing them,
then you probably want two
different functions for that. The type system
will automatically guide you to choose the right function
to use in each situation.
But if having a name is something significant about the
whole purpose of your program, and a Human and a Building
are really pretty much the same thing in that respect as far as your program
is concerned, then you would define their type together:
data NameableThing =
Human { name :: String } |
Building { name :: String }
That gives you a polymorphic function name that works for
whatever particular flavor of NameableThing you happen to have,
without needing to get into type classes.
Usually you would use a type class for a different kind of situation:
if you have some kind of non-trivial operation that has the same purpose
but a different implementation for several different types.
Even then, it's often better to use some other approach instead, like
passing a function as a parameter (a "higher order function", or "HOF").
Haskell type classes are a beautiful and powerful tool, but they are totally
different than what is called a "class" in object-oriented languages,
and they are used far less often.
And I certainly don't recommend complicating your program by using an advanced
extension to Haskell like Existential Qualification just to fit into
an object-oriented design pattern.
You can try to use Existentially Quanitified types and do it like this:
data T = forall a. Nameable a => MkT a
items = [MkT (Human "bla"), MkT (Building "bla")]
I've just had a look at the code that this question is abstracting from. For this, I would recommend merging the Task and RecurringTaskDefinition types:
data Task
= Once
{ name :: String
, scheduled :: Maybe Day
, category :: TaskCategory
}
| Recurring
{ name :: String
, nextOccurrence :: Day
, frequency :: RecurFrequency
}
type ProgramData = [Task] -- don't even need a new data type for this any more
Then, the name function works just fine on either type, and the functions you were complaining about like deleteTask and deleteRecurring don't even need to exist -- you can just use the standard delete function as usual.

Resources