Combining Tuples in SBV? - haskell

Basically I'm wondering, is there any way to write a function of the following type with the SBV library:
(SBV a, SBV b) -> SBV (a,b)
This seems like it should be possible: if we have two symbolic values, we can make a new symbolic value, as a concrete pair whose elements are either the symbolic or concrete values of the two inputs. But I can't find anything like this, and the SBV type does not have its constructors exposed.
Is this possible?

Sounds like you need the tuple function. Here's an example:
import Data.SBV
import Data.SBV.Tuple
tup :: (SymVal a, SymVal b) => (SBV a, SBV b) -> SBV (a, b)
tup = tuple
tst :: Predicate
tst = do x <- sInteger "x"
y <- sInteger "y"
z <- sTuple "xy"
return $ tup (x, y) .== z
Of course, tuple itself can handle arity upto 8; the above is just one instantiation at the exact type you wanted. We have:
$ ghci a.hs
GHCi, version 8.6.4: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Main ( a.hs, interpreted )
Ok, one module loaded.
*Main> sat tst
Satisfiable. Model:
x = 0 :: Integer
y = 1 :: Integer
xy = (0,1) :: (Integer, Integer)
There's also the untuple function that goes in the other direction. They are both in the Data.SBV.Tuple module that you have to explicitly import. (You can also find lens-like accessors in the same module, which lets you write, ^._1, ^._2 etc. to extract fields of tuples; as in z^._2 for the above example.)

Related

Conditions on list comprehension using Haskell and SBV

I want to write a Haskell list comprehension with a condition on symbolic expressions (SBV). I reproduced the problem with the following small example.
import Data.SBV
allUs :: [SInteger]
allUs = [0,1,2]
f :: SInteger -> SBool
f 0 = sTrue
f 1 = sFalse
f 2 = sTrue
someUs :: [SInteger]
someUs = [u | u <- allUs, f u == sTrue]
with show someUs, this gives the following error
*** Data.SBV: Comparing symbolic values using Haskell's Eq class!
***
*** Received: 0 :: SInteger == 0 :: SInteger
*** Instead use: 0 :: SInteger .== 0 :: SInteger
***
*** The Eq instance for symbolic values are necessiated only because
*** of the Bits class requirement. You must use symbolic equality
*** operators instead. (And complain to Haskell folks that they
*** remove the 'Eq' superclass from 'Bits'!.)
CallStack (from HasCallStack):
error, called at ./Data/SBV/Core/Symbolic.hs:1009:23 in sbv-8.8.5-IR852OLMhURGkbvysaJG5x:Data.SBV.Core.Symbolic
Changing the condition into f u .== sTrue also gives an error
<interactive>:8:27: error:
• Couldn't match type ‘SBV Bool’ with ‘Bool’
Expected type: Bool
Actual type: SBool
• In the expression: f u .== sTrue
In a stmt of a list comprehension: f u .== sTrue
In the expression: [u | u <- allUs, f u .== sTrue]
How to get around this problem?
Neither your f nor your someUs are symbolically computable as written. Ideally, these should be type-errors, rejected out-of-hand. This is due to the fact that symbolic values cannot be instances of the Eq class: Why? Because determining equality of symbolic values requires a call to the underlying solver; so the result cannot be Bool; it should really be SBool. But Haskell doesn't allow generalized guards in pattern-matching to allow for that possibility. (And there are good reasons for that too, so it's not really Haskell's fault here. It's just that the two styles of programming don't work well all that great together.)
You can ask why SBV makes symbolic values an instance of the Eq class. The only reason why it's an instance of Eq is what the error message is telling you: Because we want them to be instances of the Bits class; which has Eq as a superclass requirement. But that's a whole another discussion.
Based on this, how can you write your functions in SBV? Here's how you'd code f in the symbolic style:
f :: SInteger -> SBool
f i = ite (i .== 0) sTrue
$ ite (i .== 1) sFalse
$ ite (i .== 2) sTrue
$ sFalse -- arbitrarily filled to make the function total
Ugly, but this is the only way to write it unless you want to play some quasi-quoting tricks.
Regarding someUs: This isn't something you can directly write symbolically either: This is known as a spine-concrete list. And there's no way for SBV to know how long your resulting list would be without actually running the solver on individual elements. In general you cannot do filter like functions on a spine-concrete list with symbolic elements.
The solution is to use what's known as a symbolic list and a bounded-list abstraction. This isn't very satisfactory, but is the best you can do to avoid termination problems:
{-# LANGUAGE OverloadedLists #-}
import Data.SBV
import Data.SBV.List
import Data.SBV.Tools.BoundedList
f :: SInteger -> SBool
f i = ite (i .== 0) sTrue
$ ite (i .== 1) sFalse
$ ite (i .== 2) sTrue
$ sFalse -- arbitrarily filled to make the function total
allUs :: SList Integer
allUs = [0,1,2]
someUs :: SList Integer
someUs = bfilter 10 f allUs
When I run this, I get:
*Main> someUs
[0,2] :: [SInteger]
But you'll ask what's that number 10 in the call to bfilter? Well, the idea is that all lists are assumed to have some sort of an upper bound on their length, and the Data.SBV.Tools.BoundedList exports a bunch of methods to deal with them easily; all taking a bound parameter. So long as the inputs are at most this length long, they'll work correctly. There's no guarantee as to what happens if your list is longer than the bound given. (In general it'll chop off your lists at the bound, but you should not rely on that behavior.)
There's a worked-out example of uses of such lists in coordination with BMC (bounded-model-checking) at https://hackage.haskell.org/package/sbv-8.12/docs/Documentation-SBV-Examples-Lists-BoundedMutex.html
To sum up, dealing with lists in a symbolic context comes with some costs in modeling and how much you can do, due to restrictions in Haskell (where Bool is a fixed type instead of a class), and underlying solvers, which cannot deal with recursively defined functions all that well. The latter is mainly due to the fact that such proofs require induction, and SMT-solvers cannot do induction out-of-the-box. But if you follow the rules of the game using BMC like ideas, you can handle practical instances of the problem up to reasonable bounds.
(.==) takes two instances of EqSymbolic, returning an SBool. Inside a list comprehension, conditionals are implemented using the guard function.
Here's what it looks like:
guard :: Alternative f => Bool -> f ()
guard False = empty
guard True = pure ()
For lists, empty is [], and pure () returns a singleton list [()]. Any member of the list that evaluates to False will return an empty list instead of a unit item, excluding it from computations down the chain.
[True, False, True] >>= guard
= concatMap guard [True, False, True]
= concat $ map guard [True, False, True]
= concat $ [[()], [], [()]]
= [(), ()]
The second branch is then excluded when the context is flattened, so it's "pruned" from the computation.
It seems like you have two problems here - when you pattern match in f, you're doing a comparison using the Eq class. That's where the SBV error is coming from. Since your values are close together, you could use select, which takes a list of items, a default, an expression which evaluates to an index, and attempt to take the indexth item from that list.
You could rewrite f as
f :: SInteger -> SBool
f = select [sTrue, sFalse, sTrue] sFalse
The second problem is that guards explicitly look for Bool, but (.==) still returns an SBool. Looking at Data.SBV, you should be able to coerce that into a regular Bool using unliteral, which attempts to unwrap an SBV value into an equivalent Haskell one.
fromSBool :: SBool -> Bool
fromSBool = fromMaybe False . unliteral
someUs :: [SInteger]
someUs = [u | u <- allUs, fromSBool (f u)]
-- [0 :: SInteger, 2 :: SInteger]

Special runtime representation of [] type?

Consider the simple definition of a length-indexed vector:
data Nat = Z | S Nat
infixr 5 :>
data Vec (n :: Nat) a where
V0 :: Vec 'Z a
(:>) :: a -> Vec n a -> Vec ('S n) a
Naturally I would at some point need the following function:
vec2list :: Vec n a -> [a]
However, this function is really just a fancy identity. I believe that the runtime representations of these two types are the same, so
vec2list :: Vec n a -> [a]
vec2list = unsafeCoerce
should work. Alas, it does not:
>vec2list ('a' :> 'b' :> 'c' :> V0)
""
Every input simply returns the empty list. So I assume my understand is lacking. To test it, I define the following:
data List a = Nil | Cons a (List a) deriving (Show)
vec2list' :: Vec n a -> List a
vec2list' = unsafeCoerce
test1 = vec2list' ('a' :> 'b' :> 'c' :> V0)
data SomeVec a = forall n . SomeVec (Vec n a)
list'2vec :: List a -> SomeVec a
list'2vec x = SomeVec (unsafeCoerce x)
Surprisingly this works! It certainly isn't an issue with the GADT then (my initial thought).
I think that the List type is really identical at runtime to []. I try to test this too:
list2list :: [a] -> List a
list2list = unsafeCoerce
test2 = list2list "abc"
and it works! Based on this fact, I have to conclude that [a] and List a must have the same runtime representation. And yet, the following
list2list' :: List a -> [a]
list2list' = unsafeCoerce
test3 = list2list' (Cons 'a' (Cons 'b' (Cons 'c' Nil)))
does not work. list2list' again always returns the empty list. I believe that "having identical runtime representations" must be a symmetric relation, so this doesn't seem to make sense.
I began to think maybe there's something funny with "primitive" types - but I always believed that [] is only special syntactically, not semantically. It seems that's the case:
data Pair a b = Pair a b deriving (Show, Eq, Ord)
tup2pair :: (a,b) -> Pair a b
tup2pair = unsafeCoerce
pair2tup :: Pair a b -> (a,b)
pair2tup = unsafeCoerce
The first function works and the second does not - same as the in the case of List and []. Although in this case, pair2tup segfaults as opposed to always returning the empty list.
It seems to be consistently asymmetric with respect to types which use "built-in" syntax. Back to the Vec example, the following
list2vec :: [a] -> SomeVec a
list2vec x = SomeVec (unsafeCoerce x)
works just fine as well! The GADT really isn't special.
The question is: how do the runtime representations of types which use "built-in" syntax differ from those that do not?
Alternatively, how does one write a zero-cost coercion from Vec n a to [a]? This doesn't answer the question but solves the problem.
Testing was done with GHC 7.10.3.
As noted by a commenter, this behaviour is only present when interpreting. When compiled, all functions work as expected. The question still applies, just to runtime representation when interpreting.
Now to answer your main question, this thread appears to have the answer: start ghci with -fobject-code:
$ ghci /tmp/vec.hs
GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Main ( /tmp/vec.hs, interpreted )
Ok, modules loaded: Main.
*Main> print $ vec2list ('a' :> 'b' :> 'c' :> V0)
""
With -fobject-code:
$ ghci -fobject-code /tmp/vec.hs
GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Main ( /tmp/vec.hs, /tmp/vec.o )
Ok, modules loaded: Main.
Prelude Main> print $ vec2list ('a' :> 'b' :> 'c' :> V0)
"abc"
The modules that contain [] and (,) are all compiled, which causes their runtime representation to be different from isomorphic datatypes in interpreted modules. According to Simon Marlow on the thread I linked, interpreted modules add annotations for the debugger. I think this also explains why tup2pair works and pair2tup doesn't: missing annotations isn't a problem for interpreted modules, but the compiled modules choke on the extra annotations.
-fobject-code has some downsides: longer compilation time, only brings exported functions in scope, but it has the additional advantage that running the code is much faster.
To answer only your alternative question, you could create a newtype with a non-exported constructor to give a list a type-level length and a zero-cost coercion to lists:
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE DataKinds #-}
module Vec (Nat(..), Vec, v0, (>:>), vec2list) where
data Nat = Z | S Nat
newtype Vec (n :: Nat) a = Vec { unVec :: [a] }
v0 :: Vec Z a
v0 = Vec []
infixr 5 >:>
(>:>) :: a -> Vec n a -> Vec ('S n) a
a >:> (Vec as) = Vec (a : as)
vec2list :: Vec n a -> [a]
vec2list (Vec as) = as
As long as the Vec constructor is not in scope (so only v0 and >:> can be used to construct vectors) the invariant that the type-level number represents the length can't be violated.
(This approach definitely has my preference over unsafeCoerce, as anything with unsafeCoerce could break with every update of GHC or on different platforms.)

What does '#' mean in Haskell?

I've tried googling but come up short. I am furthering my Haskell knowledge by reading some articles and I came across one that uses a syntax I've never seen before.
An example would be:
reconstruct node#(Node a b c l r) parent#(Node b d le ri)
I've never seen these #'s before. I tried searching online for an answer but came up short. Is this simply a way to embed tags to help make things clearer, or do they have an actual impact on the code?
It is used in pattern matching. Now node variable will refer to the entire Node data type for the argument Node a b c l r. So instead of passing to the function as Node a b c l r, you can use node instead to pass it up.
A much simpler example to demonstrate it:
data SomeType = Leaf Int Int Int | Nil deriving Show
someFunction :: SomeType -> SomeType
someFunction leaf#(Leaf _ _ _) = leaf
someFunction Nil = Leaf 0 0 0
The someFunction can also be written as:
someFunction :: SomeType -> SomeType
someFunction (Leaf x y z) = Leaf x y z
someFunction Nil = Leaf 0 0 0
See how simpler was the first version ?
Using #t as a type indicator
Besides the argument pattern matching usage described in the answer of #Sibi, in Haskell the "at" character ('#', also known as an arobase character) can be used in some contexts to force a typing decision. This is mentioned in the comments by #Josh.F.
This is not part of the default language features, and is known as the Type Application Haskell language extension. In summary, the extension allows you to give explicit type arguments to a polymorphic function such as read. In a classic .hs source file, the relevant pragma must be included:
{-# LANGUAGE TypeApplications #-}
Example:
$ ghci
GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help
λ>
λ> let x = (read #Integer "33")
<interactive>:4:10: error:
Pattern syntax in expression context: read#Integer
Did you mean to enable TypeApplications?
λ>
λ> :set -XTypeApplications
λ>
λ> let x = (read #Integer "33")
λ>
λ> :type x
x :: Integer
λ>
λ> x
33
λ>
Further details
For the read polymorphic function, the type indicator introduced by # relates to the type of the result returned by read. But this is not generally true.
Generally speaking, you have to consider the type variables that appear in the type signature of the function at hand. For example, let's have a look at the fmap library function.
fmap :: Functor ft => (a -> b) -> ft a -> ft b
So here, we have 3 type variables, in order of appearance: ft, a, b. If we specialize fmap like this:
myFmap = fmap #type1 #type2 #type3
then type1 will relate to ft, type2 will relate to a and type3 will relate to b. Also, there is a special dummy type indicator #_ which means: “here, any type goes”.
For example, we can force the output type of fmap to be Integer and the functor to be the plain list [], leaving the input type a unspecified:
λ>
λ> myFmap = fmap #[] #_ #Integer
λ>
λ> :type myFmap
myFmap :: (_ -> Integer) -> [_] -> [Integer]
λ>
As for the read function, its type is:
read :: Read a => String -> a
So there is only room for one type indicator, and it relates to the type of the result returned by read, as displayed above.

No instance for (Integral [t0]) error in Haskell code

I'm getting an error:
No instance for (Integral [t0]) when I run this haskell code.
boomBangs xs = [(a,b,c) |a<-[1..xs],b<-[1..xs],c<-[1..xs], xs <- xs `div` 2]
Where am I going wrong?
The problem is that you're trying to divide a list. In particular, xs `div` 2 is the incorrect expression.
You can get this from the error message: it's complaining that [t0] does not behave like an integer (e.g. it isn't in the Integral class). [t0] is just a list of stuff--the t0, being in lowercase, is a type variable that represntes any type.
Since lists of stuff aren't numbers, we can't really know how to divide them.
You can see why you get this exact error message by looking at the type of div:
div :: Integral i => i -> i -> i
All this means is that given some type i in the Integral class, you can divide two of them together to get a third. Since lists of things are not part of the integral class, you can't divide them and so you get an error.
If div had a concrete type like div :: Int -> Int -> Int, you would get an error telling you that it can't match the expected type Int with the actual type [t0]. However, since the type actually contains a variable i, the error is a bit more complex: [t0] cannot be a valid type to use in place of i because it is not in the Integral class.
What you said was:
Give me a tuple of a, b, and c:
[ (a, b, c)
For each a, b, and c in the list of values from 1 to xs1:
| a <- [1..xs1]
, b <- [1..xs1]
, c <- [1..xs1]
For each xs2 in the quotient of xs1 and 2.
, xs2 <- xs1 `div` 2
]
If you compile with warnings enabled (-Wall) or turn them on in GHCi (:set -Wall) then you’ll get a warning that the xs in xs <- ... shadows the xs in boomBangs xs = ..., and also that it’s unused. Obviously this kind of warning can be very helpful, as it points right to your problem.
Since xs1 is the input to your function, you end up with a type like this:
(Integral [t]) => [t] -> [([t], [t], [t])]
Which is to say that the function takes a list (xs1) that can act as a number ((`div` 2)) and gives you back a list of tuples of such lists. Even though you’re trying to divide a list by a number, GHC allows it and infers a more general type because you could have defined an Integral instance for lists. It only discovers that you haven’t when you actually try to use the function on a concrete type. Writing down type signatures can help keep the compiler grounded and give you better error messages.
I can only guess you meant for boomBangs to have a type like:
Integral t => [t] -> [(t, t, t)]
Or just:
[Int] -> [(Int, Int, Int)]
In which case maybe you were thinking of something like this:
[ (a, b, c)
| x <- xs
, a <- [1..x `div` 2]
, b <- [1..x `div` 2]
, c <- [1..x `div` 2]
]

What type signature do I need to allow a list of functions to be converted to haskell code? [duplicate]

This question already has answers here:
Closed 10 years ago.
Possible Duplicate:
Why is such a function definition not allowed in haskell?
I made a haskell function called funlist. What it does is it takes a starting value, and a list of functions, and applies all of the functions in the list to the starting value.
funlist thing [function] = function thing
funlist thing (function:functions) = funlist (function thing) functions
funlist _ _ = error "need a list of functions"
The problem with this function is that it has a type of funlist :: t -> [t -> t] -> t. That type means that while ghc will allow a list of functions that don't convert the starting value to a completely different type (e.g [sin,cos,tan] will be allowed), a function that converts the starting value to a different type (e.g show) will generate an error because that function doesn't match the type signature.
This isn't how the function should work. It should be able to take a list of functions that change the starting values type (e.g. [sin,show]). This function basically converts funlist 5 [sin,cos,tan,isInfinite,show] to show $ isInfinite $ tan $ cos $ sin $ 5, and while the latter works, the former doesn't.
Is there any way that I can get this function to work properly?
EDIT: I know about . and >>>, I'm just wondering if there's a way to make this work.
You can write what you want with a GADT:
{-# LANGUAGE GADTs #-}
module Funlist where
data F x y where
Id :: F a a
Ap :: (a->b) -> F b c -> F a c
-- A very round about way to write f x = x + x
f1 :: Int -> Char
f1 = toEnum
f2 :: Char -> String
f2 x = x:x:[]
f3 :: String -> [Int]
f3 = map fromEnum
f4 :: [Int] -> Integer
f4 = foldr (+) 0 . map toInteger
f_list :: F Int Integer
f_list = Ap f1 (Ap f2 (Ap f3 (Ap f4 Id)))
ap :: F a b -> a -> b
ap Id x = x
ap (Ap f gs) x = ap gs (f x)
Now ap f_list 65 is 130
This does not work with normal functions/normal lists in Haskell, since it requires a dynamically typed language, and not a statically typed language like Haskell. The funlist function can't have a different type depending on what the contents of the function list is at runtime; its type must be known at compile-time. Further, the compiler must be able to check that the function chain is valid, so that you can't use the list [tan, show, sin] for example.
There are two solutions to this problem.
You can either use heterogenous lists. These lists can store lists where each element is a different type. You can then check the constraint that each element must be a function and that one elements return type must be the next function's parameter type. This can become very difficult very quickly.
You can also use Data.Dynamic to let your functions take and return dynamic types. You have to perform some dynamic type casts in that case.
If all you're going to do with this list of functions is apply them to a single value in a pipeline, then instead of writing and calling your funlist function, do this:
show . isInfinite . tan . cos . sin $ 5
or, if you don't want the list reversed in your code, do this:
import Control.Arrow (>>>)
(sin >>> cos >>> tan >>> isInfinite >>> show) 5
Functions in Haskell, in general, have types that look like a -> b, for some choice of a and b. In your case, you have a list [f0, ..., fn] of functions, and you want to compute this:
funlist [f0, ..., fn] x == f0 (funlist [f1, ..., fn] x)
== f0 (f1 (funlist [f2, ..., fn] x))
...
== f0 (f1 (... (fn x)))
The t -> t problem you're having is a consequence of these two things:
This computation requires the argument type of f0 to be the return type of f1, the argument type of f1 to be the return type of f2, and so on: f0 :: y -> z, f1 :: x -> y, ..., fn :: a -> b.
But you're putting all those functions in a list, and all the elements of a list in Haskell must have the same type.
These two, taken together, imply that the list of functions used in funlist must have type [t -> t], because that's the only way both conditions can be met at the same time.
Other than that, dave4420's answer is the best simple answer, IMO: use function composition. If you can't use it because the computation to be done is only known at runtime, then you want to have some data structure more complex than the list to represent the possible computations. Chris Kuklewicz presents a very generic solution for that, but I'd normally do something custom-made for the specific problem area at hand.
Also good to know that your funlist can be written like this:
funlist :: a -> [a -> a] -> a
funlist x fs = foldr (.) id fs x
Short answer: No, there's no way to do what you want with lists (in a sensible way, at least).
The reason is that lists in Haskell are always homogenous, i.e. each element of a list must have the same type. The functions you want to put to the list have types:
sin :: Floating a => a -> a
isInfinite :: Floating b => b -> Bool
show :: Show c => c -> String
So you can't just put the functions in the same list. Your two main options are to:
Use a structure other than list (e.g. HList or a custom GADT)
Use dynamic typing
Since the other answers already gave GADT examples, here's how you could implement your function using dynamic types:
import Data.Dynamic
funlist :: Dynamic -> [Dynamic] -> Dynamic
funlist thing (function:functions) = funlist (dynApp function thing) functions
funlist thing [] = thing
However, using dynamic types causes some boilerplate, because you have to convert between static and dynamic types. So, to call the function, you'd need to write
funlist (toDyn 5) [toDyn sin, toDyn cos, toDyn tan, toDyn isInfinite, toDyn show]
And unfortunately, even that is not enough. The next problem is that dynamic values must have homomorphic types, so for example instead of the function show :: Show a => a -> String you need to manually specify e.g. the concrete type show :: Bool -> String, so the above becomes:
funlist (toDyn (5::Double)) [toDyn sin, toDyn cos, toDyn tan, toDyn isInfinite,
toDyn (show :: Bool -> String)]
What's more, the result of the function is another dynamic value, so we need to convert it back to a static value if we want to use it in regular functions.
fromDyn (funlist (toDyn (5::Double)) [toDyn sin, toDyn cos, toDyn tan,
toDyn isInfinite, toDyn (show :: Bool -> String)]) ""
What you want works in Haskell, but it's not a list. It is a function composition and can actually be wrapped in a GADT:
import Control.Arrow
import Control.Category
import Prelude hiding ((.), id)
data Chain :: * -> * -> * where
Chain :: (a -> c) -> Chain c b -> Chain a b
Id :: Chain a a
apply :: Chain a b -> a -> b
apply (Chain f k) x = apply k (f x)
apply Id x = x
Now you can inspect the structure of the function chain to some extent. There isn't much you can find out, but you can add further meta information to the Chain constructor, if you need more.
The type also forms an interesting category that preserves the additional information:
instance Category Chain where
id = Id
Id . c = c
c . Id = c
c2 . Chain f1 k1 = Chain f1 (c2 . k1)
instance Arrow Chain where
arr f = Chain f Id
first (Chain f c) = Chain (first f) (first c)
first Id = Id
There where some answers using GADTs, which is a good way to do such things. What I want to add here is that the structure used in these answers already exists in a more general fashion: it's called a thrist ("type threaded list"):
Prelude Data.Thrist> let fs = Cons (show :: Char -> String) (Cons length Nil)
Prelude Data.Thrist> let f = foldl1Thrist (flip (.)) fs
Prelude Data.Thrist> :t fs
fs :: Thrist (->) Char Int
Prelude Data.Thrist> :t f
f :: Char -> Int
Prelude Data.Thrist> f 'a'
3
Of course, you could also use foldl1Thrist (>>>) fs instead. Note that thrists form a category, an arrow and a monoid (with appendThrist).

Resources