Coming from C++, I'm used to be able to build simple forms of compile-time assertions, where I could emit warnings or errors during compilation if some simple conditions (e.g. over simple algebraic expressions) weren't met via use of template meta-programming and/or cpp(1)
For instance, if I wanted to make sure my program compiles only when Int has at least a certain minBound/maxBound range or alternatively, if a loss-free (as in reversible) conversion from Int64 to Int is possible with the current compilation target. Is this possible with some GHC Haskell extension? My first guess would have been to use TH. Are there other GHC facilities that could be exploited to this end?
Here's a generalized and slightly simplified version of Anthony's example:
{-# LANGUAGE TemplateHaskell #-}
module StaticAssert (staticAssert) where
import Control.Monad (unless)
import Language.Haskell.TH (report)
staticAssert cond mesg = do
unless cond $ report True $ "Compile time assertion failed: " ++ mesg
return [] -- No need to make a dummy declaration
Usage:
{-# LANGUAGE TemplateHaskell #-}
import StaticAssert
$(staticAssert False "Not enough waffles")
Using TH for this isn't too bad. Here is a module that defines the desired assertion as part of a vestigial declaration:
{-# LANGUAGE TemplateHaskell #-}
module CompileTimeWarning where
import Control.Monad (unless)
import Data.Int (Int64)
import Language.Haskell.TH
assertInt = let test = fromIntegral (maxBound::Int) == (maxBound::Int64)
in do unless test $ report True "Int is not safe!"
n <- newName "assertion"
e <- fmap NormalB [|()|]
return $ [FunD n [Clause [] e []]]
Using the assertion involves a top-level declaration that isn't used for anything other than the assertion:
{-# LANGUAGE TemplateHaskell #-}
import CompileTimeWarning
$(assertInt)
Related
I do not understand why the DuplicateRecordFields language pragma is causing a compile time error in a template haskell splice.
Example:
-- TypeModule.hs
{-# LANGUAGE DuplicateRecordFields #-}
module TypeModule where
data A = A {foo :: Int} deriving Show
-- ThModule.hs
{-# LANGUAGE TemplateHaskell #-}
module ThModule where
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
import TypeModule
mkLambda :: Q [Dec]
mkLambda = [d| func :: A -> Int; func = foo |]
-- Lib.hs
module Lib where
import TypeModule
import ThModule
$mkLambda
{-
Illegal variable name: ‘$sel:foo:A’
When splicing a TH declaration: func_0 = (TypeModule.$sel:foo:A)
|
8 | $mkLambda
| ^^^^^^^^
-}
When I remove the DuplicateRecordFields pragma, the compile time error goes away.
I am using the DuplicateRecordFields pragma because I am parsing a number of different JSON objects which are responses from a REST API, and many of these JSON objects contain fields with identical names.
Right now I am looking for a way that does not use DuplicateRecordFields, but at the least I would like to understand what in particular is causing the compiler trouble.
This seems to be a known GHC issue: https://gitlab.haskell.org/ghc/ghc/-/issues/14848
I've got the following application:
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Main where
-- Scotty
import qualified Web.Scotty as S
import Network.Wai.Middleware.RequestLogger
import Network.Wai.Middleware.Static
import qualified Data.Text.Lazy as L
-- HTML rendering
import Text.Blaze.Html.Renderer.Text (renderHtml)
import qualified Text.Blaze.Html5 as H
import qualified Text.Blaze.Html5.Attributes as A
import Control.Monad.IO.Class
-- Database
import Database.Persist
import Database.Persist.Sqlite
import Database.Persist.TH
import Control.Monad.Trans.Resource (runResourceT, ResourceT)
import Control.Monad.Logger
-- URL generation
import System.Random
import Control.Monad (replicateM)
-- JSON
import Data.Map (fromList)
share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
Link
shortUrl L.Text
URLKey shortUrl
Primary shortUrl
longUrl L.Text
counter Int
deriving Show
|]
getURL :: L.Text -> IO (Maybe (Entity Link))
getURL shortId = runSqlite "links.db" $ do
maybeOriginal <- getBy $ URLKey shortId
pure maybeOriginal
-- I don't know what type to give this, that's probably the problem
addURL short long = runSqlite "links.db" $ do
insert $ Link short long
main :: IO ()
main = do
-- Connect to db and run migration
runSqlite "links.db" $ do runMigration migrateAll
S.scotty 3000 $ do
...
S.post "/shorten" $ do
-- Get URL
url <- S.param "url" :: S.ActionM L.Text
-- Generate a random short URL
randStr <- liftIO $ getRandStr 5
-- Add the urls to the database
liftIO $ addURL (L.pack randStr) url
-- Send JSON response with ID
S.json $ fromList [("id" :: String, randStr)]
I get the following error:
shortener> build (lib + exe)
Preprocessing library for shortener-0.1.0.0..
Building library for shortener-0.1.0.0..
Preprocessing executable 'shortener-exe' for shortener-0.1.0.0..
Building executable 'shortener-exe' for shortener-0.1.0.0..
[2 of 2] Compiling Main
/home/henry/haskell/shortener/app/Main.hs:86:5: error:
• Couldn't match type ‘PersistEntityBackend (Int -> Link)’
with ‘SqlBackend’
arising from a use of ‘insert’
• In the first argument of ‘($)’, namely ‘insert’
In a stmt of a 'do' block: insert $ Link short long
In the second argument of ‘($)’, namely
‘do insert $ Link short long’
|
86 | insert $ Link short long
| ^^^^^^
-- While building package shortener-0.1.0.0 (scroll up to its section to see the error) using:
/home/henry/.stack/setup-exe-cache/x86_64-linux-tinfo6/Cabal-simple_mPHDZzAJ_3.4.1.0_ghc-9.0.2 --builddir=.stack-work/dist/x86_64-linux-tinfo6/Cabal-3.4.1.0 build lib:shortener exe:shortener-exe --ghc-options " -fdiagnostics-color=always"
Process exited with code: ExitFailure 1
I'm not sure how to resolve this type error and I haven't been able to find anything of use online. There was this answer with a similar problem, but the given type signature and several variations of it did not work.
It turns out I forgot a field when inserting. I had
insert $ Link short long
I needed
insert $ Link short long 0
for the counter field of Link.
Unfortunately the error didn't make that at all clear.
So, I'm starting to experiment with quasiquotation and template haskell.
I want to modify an existing (large) quasiquotation code, while using the actual value of a variable defined where it is 'called'. To illustrate with a simple example:
main.hs
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH
import Exp02
x = "cde"
main = do
putStrLn [str|$x|]
Exp02.hs
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
module Exp02 where
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
import Language.Haskell.TH.Quote
xpto :: String -> ExpQ
xpto [] = stringE []
xpto ('$':rest) = varE (mkName rest)
xpto str = stringE str
str = QuasiQuoter
{ quoteExp = xpto
, quotePat = fail $ "patterns"
, quoteType= fail $ "types"
, quoteDec = fail $ "declarations"
}
While this compiles and prints out "cde", this is not what I want. My understanding is that the resulting code in main after splicing is: putStrLn x. What I want is to generate putStrLn cde (I know this is not valid haskell code, but it's just to represent my point).
Thus, to put it in another way, I do not want to 'create a reference to the variable x in the main file', I want to actually use its value inside the xpto quasiquoter code.
I am guessing this may not be possible, since it would imply a circular reference between main.hs and Exp02.hs, and thus face the TH stage restriction. Is this correct, or is there a way to use x value inside the xpto code?
Thanks!
No, what you are trying to do isn't currently possible. From the template haskell docs:
You can only run a function at compile time if it is imported from another module that is not part of a mutually-recursive group of modules that includes the module currently being compiled. Furthermore, all of the modules of the mutually-recursive group must be reachable by non-SOURCE imports from the module where the splice is to be run.
For example, when compiling module A, you can only run Template Haskell functions imported from B if B does not import A (directly or indirectly). The reason should be clear: to run B we must compile and run A, but we are currently type-checking A.
You are attempting to run the function (or more strictly value) x at compile time in the same module as x was defined, which is clearly stated to not be allowed.
I got sick of unpacking Data.Text instances all the time before printing them out for debugging and thought to just use Text.Printf for that. Unfortunately, I couldn't make it work:
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
import Data.Text
import Text.Printf
--instance PrintfArg Text where
-- toUPrintf = toUPrintf . unpack
main :: IO ()
main = do
let input :: Text = "abc"
printf "Input: %s\n" input
The error:
src/Main.hs:12:3:
No instance for (PrintfArg Text)
arising from a use of `printf'
Possible fix: add an instance declaration for (PrintfArg Text)
In a stmt of a 'do' block: printf "Input: %s" input
In the expression:
do { let input :: Text = "abc";
printf "Input: %s" input }
In an equation for `main':
main
= do { let input :: Text = ...;
printf "Input: %s" input }
After uncommenting the instance declaration:
src/Main.hs:7:7:
`toUPrintf' is not a (visible) method of class `PrintfArg'
src/Main.hs:7:19: Not in scope: `toUPrintf'
Any ideas?
EDITED
As suggested, tried TH, still no go:
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
import Data.Text
import Language.Haskell.TH
import Text.Printf
runQ [d| instance PrintfArg Text where toUPrintf = toUPrintf . unpack|]
main :: IO ()
main = do
let input :: Text = "abc"
printf "Input: %s\n" input
Error:
src/Main.hs:9:40:
'toUPrintf' is not a (visible) method of class 'PrintfArg'
src/Main.hs:9:52: Not in scope: 'toUPrintf'
Help! It's amazing this doesn't work out of the box given all the advice to use Data.Text by default.
WARNING: text-format is unmaintained, no response from the author in 2 years. See other answers.
I'd look at the text-format package: it is similar to Text.Printf, but specifically designed for Data.Text.Lazy.
There are a few other advantages of text-format over Text.Printf:
The Buildable class is exposed, so it can be extended to support new parameter types.
It uses a simpler approach to varargs, which sidesteps problems one has in Text.Printf with accessing the return value.
It should be much faster, for several reasons:
it never converts to the inefficient String representation;
it doesn't build intermediate datatypes, unlike UPrintf in Text.Printf;
it uses the double-conversion package for rendering Double and Float, which is about 30 times faster than Prelude's methods.
Since this question was asked, the base and text libraries have been updated to support this. If you have base >= 4.7.0.0 and text >= 1.2.2.0, then the OP's MWE actually works:
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
import Data.Text
import Text.Printf
main :: IO ()
main = do
let input :: Text = "abc"
printf "Input: %s\n" input
Output:
$ ghci
GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help
Prelude> :l test.hs
[1 of 1] Compiling Main ( test.hs, interpreted )
Ok, one module loaded.
*Main> main
Input: abc
*Main>
Leaving GHCi.
From the documentation:
The HPrintfType class provides the variable argument magic for hPrintf. Its implementation is intentionally not visible from this module.
While you could use TH to generate HPrintfType instances (because TH ignores export restrictions) the easiest solution is probably a printf' type function:
printt :: PrintType r => Text -> r
printt = printf . Data.Text.unpack
Another package worth checking out: formatting
Combinator-based type-safe formatting (like printf() or FORMAT) for Text.
Example:
format ("Person's name is " % text % ", age is " % hex) "Dave" 54
Intro:
While checking out snoyman's "persistent" library I found myself wanting ghci's (or another tool) assistance in figuring out stuff.
ghci's :info doesn't seem to work as nicely with type-families and data-families as it does with "plain" types:
> :info Maybe
data Maybe a = Nothing | Just a -- Defined in Data.Maybe
...
> :info Persist.Key Potato -- "Key Potato" defined in example below
data family Persist.Key val -- Defined in Database.Persist
... (no info on the structure/identity of the actual instance)
One can always look for the instance in the source code, but sometimes it could be hard to find it and it may be hidden in template-haskell generated code etc.
Code example:
{-# LANGUAGE FlexibleInstances, GeneralizedNewtypeDeriving, MultiParamTypeClasses, TypeFamilies, QuasiQuotes #-}
import qualified Database.Persist as Persist
import Database.Persist.Sqlite as PSqlite
PSqlite.persistSqlite [$persist|
Potato
name String
isTasty Bool
luckyNumber Int
UniqueId name
|]
What's going on in the code example above is that Template-Haskell is generating code for us here. All the extensions above except for QuasiQuotes are required because the generated code uses them.
I found out what Persist.Key Potato is by doing:
-- test.hs:
test = PSqlite.persistSqlite [$persist|
...
-- ghci:
> :l test.hs
> import Language.Haskell.TH
> import Data.List
> runQ test >>= putStrLn . unlines . filter (isInfixOf "Key Potato") . lines . pprint
where newtype Database.Persist.Key Potato = PotatoId Int64
type PotatoId = Database.Persist.Key Potato
Question:
Is there an easier way to get information on instances of type families and data families, using ghci or any other tool?
Does -ddump-splices show you the TH-generated code in this case?
Otherwise, :browse does give you info about data family instances, though not about type families.
You might want to file a ghc ticket - the :browse output looks mangled, and one might expect data family instances to be reported like class instances, by :info.