I just start learning Template Haskell, and stuck on simple problem with splicing.
In one module I've implemented function tupleN which replies N-th element of the tuple:
tupleN :: Lift a => a -> Int -> Q Exp
tupleN a n = do
(TupE as) <- lift a
return $ as !! n
In the Main module I have:
main :: IO ()
main = do
let tup = (1::Int,'a',"hello")
putStrLn $ show $(tupleN $tup 1)
This seems to be working, but it wouldn't. Compiler prints error:
GHC stage restriction: `tup'
is used in a top-level splice or annotation,
and must be imported, not defined locally
In the expression: tup
In the first argument of `tupleN', namely `$tup'
In the expression: tupleN ($tup) 1
If I put tuple description right into spliced expression, code become working:
main :: IO ()
main = do
putStrLn $ show $(tupleN (1::Int,'a',"hello") 1)
What I missing with the first variant?
You've tried to use tup as a splice, but tup is just an ordinary value. You don't want to prefix it with a $.
Moreover, as the compile error states, since Template Haskell runs during the compilation process, GHC really needs to know what it's doing before it has finished compiling the current module. That means your splice expression can't depend on tup, because that's still being compiled. Inside splices, you can only use literals, imported values, and the special 'name and ''TypeName forms (which you can think of as a sort of literal, I suppose). You can get at some of the information from this compilation by using e.g. reify, but even that can only give you data that's available at compile time – if you want a function you can pass user input, or data constructed from user input, to, that's just impossible.
In short, you can't do exactly what you want to do using Template Haskell. You could, however, define a splice that expands to a function to get the ith element of a tuple of size sz:
import Control.Monad (unless)
import Language.Haskell.TH
tupleN :: Int -> Int -> Q Exp
tupleN sz i = do
unless (i < sz) . reportError $ "tupleN: index " ++ show i
++ " out of bounds for " ++ show sz ++ "-tuple"
lamE
[tupP (replicate i wildP
++ [varP (mkName "x")]
++ replicate (sz - i - 1) wildP)]
(varE (mkName "x"))
Related
I beg for your help, speeding up the following program:
main = do
jobsToProcess <- fmap read getLine
forM_ [1..jobsToProcess] $ \_ -> do
[r, k] <- fmap (map read . words) getLine :: IO [Int]
putStrLn $ doSomeReallyLongWorkingJob r k
There could(!) be a lot of identical jobs to do, but it's not up to me modifying the inputs, so I tried to use Data.HashMap for backing up already processed jobs. I already optimized the algorithms in the doSomeReallyLongWorkingJob function, but now it seems, it's quite as fast as C.
But unfortunately it seems, I'm not able to implement a simple cache without producing a lot of errors. I need a simple cache of Type HashMap (Int, Int) Int, but everytime I have too much or too few brackets. And IF I manage to define the cache, I'm stuck in putting data into or retrieving data from the cache cause of lots of errors.
I already Googled for some hours but it seems I'm stuck. BTW: The result of the longrunner is an Int as well.
It's pretty simple to make a stateful action that caches operations. First some boilerplate:
{-# LANGUAGE FlexibleContexts #-}
import Control.Monad.State
import Data.Map (Map)
import qualified Data.Map as M
import Debug.Trace
I'll use Data.Map, but of course you can substitute in a hash map or any similar data structure without much trouble. My long-running computation will just add up its arguments. I'll use trace to show when this computation is executed; we'll hope not to see the output of the trace when we enter a duplicate input.
reallyLongRunningComputation :: [Int] -> Int
reallyLongRunningComputation args = traceShow args $ sum args
Now the caching operation will just look up whether we've seen a given input before. If we have, we'll return the precomputed answer; otherwise we'll compute the answer now and store it.
cache :: (MonadState (Map a b) m, Ord a) => (a -> b) -> a -> m b
cache f x = do
mCached <- gets (M.lookup x)
case mCached of
-- depending on your goals, you may wish to force `result` here
Nothing -> modify (M.insert x result) >> return result
Just cached -> return cached
where
result = f x
The main function now just consists of calling cache reallyLongRunningComputation on appropriate inputs.
main = do
iterations <- readLn
flip evalStateT M.empty . replicateM_ iterations
$ liftIO getLine
>>= liftIO . mapM readIO . words
>>= cache reallyLongRunningComputation
>>= liftIO . print
Let's try it in ghci!
> main
5
1 2 3
[1,2,3]
6
4 5
[4,5]
9
1 2
[1,2]
3
1 2
3
1 2 3
6
As you can see by the bracketed outputs, reallyLongRunningComputation was called the first time we entered 1 2 3 and the first time we entered 1 2, but not the second time we entered these inputs.
I hope i'm not too far off base, but first you need a way to carry around the past jobs with you. Easiest would be to use a foldM instead of a forM.
import Control.Monad
import Data.Maybe
main = do
jobsToProcess <- fmap read getLine
foldM doJobAcc acc0 [1..jobsToProcess]
where
acc0 = --initial value of some type of accumulator, i.e. hash map
doJobAcc acc _ = do
[r, k] <- fmap (map read . words) getLine :: IO [Int]
case getFromHash acc (r,k) of
Nothing -> do
i <- doSomeReallyLongWorkingJob r k
return $ insertNew acc (r,k) i
Just i -> do
return acc
Note, I don't actually use the interface for putting and getting the hash table key. It doesn't actually have to be a hash table, Data.Map from containers could work. Or even a list if its going to be a small one.
Another way to carry around the hash table would be to use a State transformer monad.
I am just adding this answer since I feel like the other answers are diverging a bit from the original question, namely using hashtable constructs in Main function (inside IO monad).
Here is a minimal hashtable example using hashtables module. To install the module with cabal, simply use
cabal install hashtables
In this example, we simply put some values in a hashtable and use lookup to print a value retrieved from the table.
import qualified Data.HashTable.IO as H
main :: IO ()
main = do
t <- H.new :: IO (H.CuckooHashTable Int String)
H.insert t 22 "Hello world"
H.insert t 5 "No problem"
msg <- H.lookup t 5
print msg
Notice that we need to use explicit type annotation to specify which implementation of the hashtable we wish to use.
I am using the Idone.com site and wanted to run this code but do not know the syntax putStrLn to compile from stdin Use this code but strip error.
main = putStrLn (show (sumaCifras x))
sumaCifras:: Int -> Int
sumaCifras x = div x 1000 + mod (div x 100) 10 + mod (div x 10) 10 + mod x 10
Compiler is having a problem, because you use x in main function, which isn't bound in this scope. At first you must read a value from input and then pass it to your function. You can do it in 2 ways.
More natural for people used to imperative languages is "do" syntax, in which it will look like that:
main = do
x <- getLine
putStrLn (show (sumaCifras (read x :: Int)))
When you want to use x as Int, you must use "read" function with type signature, so compiler will know what to expect.
To write it in more functional way, you may use monad transformations, to pass it like that
main = getLine >>= (\x -> putStrLn(show (sumaCifras (read x :: Int)))
The ">>=" operator will get result value from first monadic action (in here it is IO action of getting input) and apply it to function on the right (in here it is lambda function that reads input as Integer, applies your function and returns it to putStrLn, which prints it on the screen). "do" syntax is essentially just a syntactic sugar for this monadic operations, so it will not affect the execution or performance of program.
You can go one step further in writing it functionally by writing it totally point-free
main = getLine >>= (putStrLn . show . sumaCifras . (read :: String -> Int))
Note that here you have type signature for read function, not for application of this function to argument, hence the String -> Int. In here first executed is the getLine function. Input obtained from it is then passed to the read, where it is casted to Int, next is sumaCifras, which then is casted to String by show and printed with putStrLn.
I have a hard time grasping this. When writing in do notation, how are the following two lines different?
1. let x = expression
2. x <- expression
I can't see it. Sometimes one works, some times the other. But rarely both. "Learn you a haskell" says that <- binds the right side to the symbol on the left. But how is that different from simply defining x with let?
The <- statement will extract the value from a monad, and the let statement will not.
import Data.Typeable
readInt :: String -> IO Int
readInt s = do
putStrLn $ "Enter value for " ++ s ++ ": "
readLn
main = do
x <- readInt "x"
let y = readInt "y"
putStrLn $ "x :: " ++ show (typeOf x)
putStrLn $ "y :: " ++ show (typeOf y)
When run, the program will ask for the value of x, because the monadic action readInt "x" is executed by the <- statement. It will not ask for the value of y, because readInt "y" is evaluated but the resulting monadic action is not executed.
Enter value for x:
123
x :: Int
y :: IO Int
Since x :: Int, you can do normal Int things with it.
putStrLn $ "x = " ++ show x
putStrLn $ "x * 2 = " ++ show (x * 2)
Since y :: IO Int, you can't pretend that it's a regular Int.
putStrLn $ "y = " ++ show y -- ERROR
putStrLn $ "y * 2 = " ++ show (y * 2) -- ERROR
In a let binding, the expression can have any type, and all you're doing is giving it a name (or pattern matching on its internal structure).
In the <- version, the expression must have type m a, where m is whatever monad the do block is in. So in the IO monad, for instance, bindings of this form must have some value of type IO a on the right-hand side. The a part (inside the monadic value) is what is bound to the pattern on the left-hand side. This lets you extract the "contents" of the monad within the limited scope of the do block.
The do notation is, as you may have read, just syntactic sugar over the monadic binding operators (>>= and >>). x <- expression de-sugars to expression >>= \x -> and expression (by itself, without the <-) de-sugars to expression >>. This just gives a more convenient syntax for defining long chains of monadic computations, which otherwise tend to build up a rather impressive mass of nested lambdas.
let bindings don't de-sugar at all, really. The only difference between let in a do block and let outside of a do block is that the do version doesn't require the in keyword to follow it; the names it binds are implicitly in scope for the rest of the do block.
In the let form, the expression is a non-monadic value, while the right side of a <- is a monadic expression. For example, you can only have an I/O operation (of type IO t) in the second kind of binding. In detail, the two forms can be roughly translated as (where ==> shows the translation):
do {let x = expression; rest} ==> let x = expression in do {rest}
and
do {x <- operation; rest} ==> operation >>= (\ x -> do {rest})
let just assigns a name to, or pattern matches on arbitrary values.
For <-, let us first step away from the (not really) mysterious IO monad, but consider monads that have a notion of a "container", like a list or Maybe. Then <- does not more than "unpacking" the elements of that container. The opposite operation of "putting it back" is return. Consider this code:
add m1 m2 = do
v1 <- m1
v2 <- m2
return (v1 + v2)
It "unpacks" the elements of two containers, add the values together, and wraps it again in the same monad. It works with lists, taking all possible combinations of elements:
main = print $ add [1, 2, 3] [40, 50]
--[41,51,42,52,43,53]
In fact in case of lists you could write as well add m1 m2 = [v1 + v2 | v1 <- m1, v2 <- m2]. But our version works with Maybes, too:
main = print $ add (Just 3) (Just 12)
--Just 15
main = print $ add (Just 3) Nothing
--Nothing
Now IO isn't that different at all. It's a container for a single value, but it's a "dangerous" impure value like a virus, that we must not touch directly. The do-Block is here our glass containment, and the <- are the built-in "gloves" to manipulate the things inside. With the return we deliver the full, intact container (and not just the dangerous content), when we are ready. By the way, the add function works with IO values (that we got from a file or the command line or a random generator...) as well.
Haskell reconciles side-effectful imperative programming with pure functional programming by representing imperative actions with types of form IO a: the type of an imperative action that produces a result of type a.
One of the consequences of this is that binding a variable to the value of an expression and binding it to the result of executing an action are two different things:
x <- action -- execute action and bind x to the result; may cause effect
let x = expression -- bind x to the value of the expression; no side effects
So getLine :: IO String is an action, which means it must be used like this:
do line <- getLine -- side effect: read from stdin
-- ...do stuff with line
Whereas line1 ++ line2 :: String is a pure expression, and must be used with let:
do line1 <- getLine -- executes an action
line2 <- getLine -- executes an action
let joined = line1 ++ line2 -- pure calculation; no action is executed
return joined
Here is a simple example showing you the difference.
Consider the two following simple expressions:
letExpression = 2
bindExpression = Just 2
The information you are trying to retrieve is the number 2.
Here is how you do it:
let x = letExpression
x <- bindExpression
let directly puts the value 2 in x.
<- extracts the value 2 from the Just and puts it in x.
You can see with that example, why these two notations are not interchangeable:
let x = bindExpression would directly put the value Just 2 in x.
x <- letExpression would not have anything to extract and put in x.
I'm trying to spew out randomly generated dice for every roll that the user plays. The user has 3 rolls per turn and he gets to play 5 turns (I haven't implemented this part yet and I would appreciate suggestions).
I'm also wondering how I can display the colors randomly. I have the list of tuples in place, but I reckon I need some function that uses random and that list to match those colors. I'm struggling as to how.
module Main where
import System.IO
import System.Random
import Data.List
diceColor = [("Black",1),("Green",2),("Purple",3),("Red",4),("White",5),("Yellow",6)]
{-
randomList :: (RandomGen g) -> Int -> g -> [Integer]
random 0 _ = []
randomList n generator = r : randomList (n-1) newGenerator
where (r, newGenerator) = randomR (1, 6) generator
-}
rand :: Int -> [Int] -> IO ()
rand n rlst = do
num <- randomRIO (1::Int, 6)
if n == 0
then doSomething rlst
else rand (n-1) (num:rlst)
doSomething x = putStrLn (show (sort x))
main :: IO ()
main = do
--hSetBuffering stdin LineBuffering
putStrLn "roll, keep, score?"
cmd <- getLine
doYahtzee cmd
--rand (read cmd) []
doYahtzee :: String -> IO ()
doYahtzee cmd = do
if cmd == "roll"
then rand 5 []
else do print "You won"
There's really a lot of errors sprinkled throughout this code, which suggests to me that you tried to build the whole thing at once. This is a recipe for disaster; you should be building very small things and testing them often in ghci.
Lecture aside, you might find the following facts interesting (in order of the associated errors in your code):
List is deprecated; you should use Data.List instead.
No let is needed for top-level definitions.
Variable names must begin with a lower case letter.
Class prerequisites are separated from a type by =>.
The top-level module block should mainly have definitions; you should associate every where clause (especially the one near randomList) with a definition by either indenting it enough not to be a new line in the module block or keeping it on the same line as the definition you want it to be associated with.
do introduces a block; those things in the block should be indented equally and more than their context.
doYahtzee is declared and used as if it has three arguments, but seems to be defined as if it only has one.
The read function is used to parse a String. Unless you know what it does, using read to parse a String from another String is probably not what you want to do -- especially on user input.
putStrLn only takes one argument, not four, and that argument has to be a String. However, making a guess at what you wanted here, you might like the (!!) and print functions.
dieRoll doesn't seem to be defined anywhere.
It's possible that there are other errors, as well. Stylistically, I recommend that you check out replicateM, randomRs, and forever. You can use hoogle to search for their names and read more about them; in the future, you can also use it to search for functions you wish existed by their type.
I'm trying to write a renamer for a compiler that I'm writing in Haskell.
The renamer scans an AST looking for symbol DEFs, which it enters into a symbol table, and symbol USEs, which it resolves by looking in the symbol table.
In this language, uses can come before or after defs, so it would seem that a 2 pass strategy is required; one pass to find all the defs and build the symbol table, and a second to resolve all the uses.
However, since Haskell is lazy (like me), I figure I can tie-the-knot and pass the renamer the final symbol table before it is actually built. This is fine as long as I promise to actually build it. In an imperative programming language, this would be like sending a message back in time. This does work in Haskell, but care must be taken to not introduce a temporal paradox.
Here's a terse example:
module Main where
import Control.Monad.Error
import Control.Monad.RWS
import Data.Maybe ( catMaybes )
import qualified Data.Map as Map
import Data.Map ( Map )
type Symtab = Map String Int
type RenameM = ErrorT String (RWS Symtab String Symtab)
data Cmd = Def String Int
| Use String
renameM :: [Cmd] -> RenameM [(String, Int)]
renameM = liftM catMaybes . mapM rename1M
rename1M :: Cmd -> RenameM (Maybe (String, Int))
rename1M (Def name value) = do
modify $ \symtab -> Map.insert name value symtab
return Nothing
rename1M (Use name) = return . liftM ((,) name) . Map.lookup name =<< ask
--rename1M (Use name) =
-- maybe (return Nothing) (return . Just . (,) name) . Map.lookup name =<< ask
--rename1M (Use name) =
-- maybe (throwError $ "Cannot locate " ++ name) (return . Just . (,) name) . Map.lookup name =<< ask
rename :: [Cmd] -> IO ()
rename cmds = do
let (result, symtab, log) = runRWS (runErrorT $ renameM cmds) symtab Map.empty
print result
main :: IO ()
main = do
rename [ Use "foo"
, Def "bar" 2
, Use "bar"
, Def "foo" 1
]
This is the line where the knot is tied:
let (result, symtab, log) = runRWS (runErrorT $ renameM cmds) symtab Map.empty
The running symbol table is stored in the MonadState of the RWS, and the final symbol table is stored in the MonadReader.
In the above example, I have 3 versions of rename1M for Uses (2 are commented out). In this first form, it works fine.
If you comment out the first rename1M Use, and uncomment the second, the program does not terminate. However, it is, in spirit, no different than the first form. The difference is that it has two returns instead of one, so the Maybe returned from Map.lookup must be evaluated to see which path to take.
The third form is the one that I really want. I want to throw an error if I can't find a symbol. But this version also does not terminate. Here, the temporal paradox is obvious; the decision about whether the the symbol will be in the table can affect whether it will be in the table...
So, my question is, is there an elegant way to do what the third version does (throw an error) without running into the paradox? Send the errors on the MonadWriter without allowing the lookup to change the path? Two passes?
Do you really have to interrupt execution when an error occurs? An alternative approach would be to log errors. After tying the knot, you can check whether the list of errors is empty. I've taken this approach in the past.
-- I've wrapped a writer in a writer transformer. You'll probably want to implement it differently to avoid ambiguity
-- related to writer methods.
type RenameM = WriterT [RenameError] (RWS Symtab String Symtab)
rename1M (Use name) = do
symtab_entry <- asks (Map.lookup name)
-- Write a list of zero or more errors. Evaluation of the list is not forced until all processing is done.
tell $ if isJust symtab_entry then [] else missingSymbol name
return $ Just (name, fromMaybe (error "lookup failed") symtab_entry)
rename cmds = do
let ((result, errors), symtab, log) = runRWS (runWriterT $ renameM cmds) symtab Map.empty
-- After tying the knot, check for errors
if null errors then print result else print errors
This does not produce laziness-related nontermination problems because the contents of the symbol table are not affected by whether or not a lookup succeeded.
I don't have a well thought out answer, but one quick thought. Your single pass over the AST takes all the Def and produces a (Map Symbol _), and I wonder if the same AST pass can take all the Use and produce a (Set Symbol) as well as the lazy lookup.
Afterwards you can quite safely compare the Symbols in the keys of the Map with the Symbols in the Set. If the Set has anything not in the Map then you can report all of those Symbols are errors. If any Def'd Symbols are not in in the Set then you can warn about unused Symbols.