Extract (a, b, c) from (Value a, Value b, Value c) - haskell

I'm using esqueleto for making SQL queries, and I have one query which returns data with type (Value a, Value b, Value c). I want to extract (a, b, c) from it. I know that I can use pattern matching like that:
let (Value a, Value b, Value c) = queryResult
But I'd like to avoid repeating Value for every tuple element. This is particularly annoying when the tuple has much more elements (like 10). Is there any way to simplify this? Is there a function which I could use like that:
let (a, b, c) = someFunction queryResult

Data.Coerce from base provides coerce, which acts as your someFunction.
coerce "exchanges" newtypes for the underlying type they wrap (and visa-versa). This works even if they are wrapped deeply within other types. This is also done with zero overhead, since newtypes have the exact same runtime representation as the type they wrap.
There is a little bit more complexity with type variable roles that you can read about on the Wiki page if you're interested, but an application like this turns out to be straightforward since the package uses the "default" role for Value's type variable argument.

The library appears to have an unValue function, so you just need to choose a way to map over arbitrary length tuples. Then someFunction can become
import Control.Lens (over, each)
someFunction = (over each) unValue
If you want to try some other ways to map tuples without a lens dependency, you could check out this question: Haskell: how to map a tuple?
edit: As danidiaz points out this only works for tuples which are max 8 fields long. I'm not sure if there's a better way to generalise it.

If your tuple has all the same element type:
all3 :: (a -> b) -> (a, a, a) -> (b, b, b)
all3 f (x, y, z) = (f x, f y, f z)
This case can be abstracted over with lenses, using over each as described in #Zpalmtree’s answer.
But if your tuple has different element types, you can make the f argument of this function polymorphic using the RankNTypes extension:
all3 :: (forall a. c a -> a) -> (c x, c y, c z) -> (x, y, z)
all3 f (x, y, z) = (f x, f y, f z)
Then assuming you have unValue :: Value a -> a, you can write:
(a, b, c) = all3 unValue queryResult
However, you would need to write separate functions all4, all5, …, all10 if you have large tuples. In that case you could cut down on the boilerplate by generating them with Template Haskell. This is part of the reason that large tuples are generally avoided in Haskell, since they’re awkward to work with and can’t be easily abstracted over.

Related

Flattening tuples in Haskell

In Haskell we can flatten a list of lists Flatten a list of lists
For simple cases of tuples, I can see how we would flatten certain tuples, as in the following examples:
flatten :: (a, (b, c)) -> (a, b, c)
flatten x = (fst x, fst(snd x), snd(snd x))
flatten2 :: ((a, b), c) -> (a, b, c)
flatten2 x = (fst(fst x), snd(fst x), snd x)
However, I'm after a function that accepts as input any nested tuple and which flattens that tuple.
Can such a function be created in Haskell?
If one cannot be created, why is this the case?
No, it's not really possible. There are two hurdles to clear.
The first is that all the different sizes of tuples are different type constructors. (,) and (,,) are not really related to each other at all, except in that they happen to be spelled with a similar sequence of characters. Since there are infinitely many such constructors in Haskell, having a function which did something interesting for all of them would require a typeclass with infinitely many instances. Whoops!
The second is that there are some very natural expectations we naively have about such a function, and these expectations conflict with each other. Suppose we managed to create such a function, named flatten. Any one of the following chunks of code seems very natural at first glance, if taken in isolation:
flattenA :: ((Int, Bool), Char) -> (Int, Bool, Char)
flattenA = flatten
flattenB :: ((a, b), c) -> (a, b, c)
flattenB = flatten
flattenC :: ((Int, Bool), (Char, String)) -> (Int, Bool, Char, String)
flattenC = flatten
But taken together, they seem a bit problematic: flattenB = flatten can't possibly be type-correct if both flattenA and flattenC are! Both of the input types for flattenA and flattenC unify with the input type to flattenB -- they are both pairs whose first component is itself a pair -- but flattenA and flattenC return outputs with differing numbers of components. In short, the core problem is that when we write (a, b), we don't yet know whether a or b is itself a tuple and should be "recursively" flattened.
With sufficient effort, it is possible to do enough type-level programming to put together something that sometimes works on limited-size tuples. But it is 1. a lot of up-front effort, 2. very little long-term programming efficiency payoff, and 3. even at use sites requires a fair amount of boilerplate. That's a bad combo; if there's use-site boilerplate, then you might as well just write the function you cared about in the first place, since it's generally so short to do so anyway.

Why is toList (1, 2) == [2]

As the question says, why is toList (1, 2) == [2]?
I remember something similar happening when fmapping on tuples, but I do not remember why or if it is related.
(1,2) does not correspend to the list [1,2]. That wouldn't make sense: what would then (True, 3.14) correspend to? You can't have the list [True, 3.14], because a list can only contain elements of a single type. (Haskell is different from e.g. Python here.)
The only way to pick elements of guaranteed a single type from any tuple is, well, to take only a single element. Hence toList, as generated from the Foldable (a,) instance, takes tuples (a,b) and yields lists [b]. Obviously there's always exactly one b element in such a tuple†.
You could in principle consider (Int, Int) as a special case where the elements have the same type and hence you can pick two instead of one, but such a special handling would require some highly awkward type-equality checking. And generally, special-case handling is not a good idea.
Arguably, it would have been better not to define the Foldable (a,) instance at all, to avoid this confusing behaviour. Then again, sometimes it's handy to use fold to just get rid of the first tuple element (e.g. some index).
†Why use b and not a? Kind of arbitrary? Well, not completely. (a,b) is actually syntactic sugar for (,) a b, hence you can consider (,) a as a functor (whose elements have type b), but you can't have a functor (`(,)`b) whose elements would have type a.
If you are planning to use homogeneous pairs heavily, you may want to declare a new type which will precisely correspond to them. This way you'll be able to have access to the toList you were expecting.
newtype Pair a = Pair { pair :: (a, a) }
instance Functor Pair where
fmap f (Pair (x, y)) = Pair (f x, f y)
instance Foldable Pair where
foldr f z (Pair (x, y)) = f x $ f y z
(a, b) is fundamentally different from Pair a or Constant (a, a) b and it is important to clearly document which one you mean in your code if you want typeclass resolution to pick the right instance.
newtype Constant a b = Constant a
instance Functor (Constant a) where
fmap f (Constant a) = Constant a
instance Foldable (Constant a) where
foldr f z _ = z
Examples:
length (Constant (1, 2)) == 0
length (1, 2) == 1
length (Pair (1, 2)) == 2
The results do make more sense when you interpret the function names like this:
length - how many values will be touched by fmap, fold etc.
toList - what elements will be touched by fmap, fold etc.
As long as
length x == length (toList x)
the world is fine.

Are there useful applications for the Divisible Type Class?

I've lately been working on an API in Elm where one of the main types is contravariant. So, I've googled around to see what one can do with contravariant types and found that the Contravariant package in Haskell defines the Divisible type class.
It is defined as follows:
class Contravariant f => Divisible f where
divide :: (a -> (b, c)) -> f b -> f c -> f a
conquer :: f a
It turns out that my particular type does suit the definition of the Divisible type class. While Elm does not support type classes, I do look at Haskell from time to time for some inspiration.
My question: Are there any practical uses for this type class? Are there known APIs out there in Haskell (or other languages) that benefit from this divide-conquer pattern? Are there any gotchas I should be aware of?
Thank you very much for your help.
One example:
Applicative is useful for parsing, because you can turn Applicative parsers of parts into a parser of wholes, needing only a pure function for combining the parts into a whole.
Divisible is useful for serializing (should we call this coparsing now?), because you can turn Divisible serializers of parts into a serializer of wholes, needing only a pure function for splitting the whole into parts.
I haven't actually seen a project that worked this way, but I'm (slowly) working on an Avro implementation for Haskell that does.
When I first came across Divisible I wanted it for divide, and had no idea what possible use conquer could be other than cheating (an f a out of nowhere, for any a?). But to make the Divisible laws check out for my serializers conquer became a "serializer" that encodes anything to zero bytes, which makes a lot of sense.
Here's a possible use case.
In streaming libraries, one can have fold-like constructs like the ones from the foldl package, that are fed a sequence of inputs and return a summary value when the sequence is exhausted.
These folds are contravariant on their inputs, and can be made Divisible. This means that if you have a stream of elements where each element can be somehow decomposed into b and c parts, and you also happen to have a fold that consumes bs and another fold that consumes cs, then you can build a fold that consumes the original stream.
The actual folds from foldl don't implement Divisible, but they could, using a newtype wrapper. In my process-streaming package I have a fold-like type that does implement Divisible.
divide requires the return values of the constituent folds to be of the same type, and that type must be an instance of Monoid. If the folds return different, unrelated monoids, a workaround is to put each return value in a separate field of a tuple, leaving the other field as mempty. This works because a tuple of monoids is itself a Monoid.
I'll examine the example of the core data types in Fritz Henglein's generalized radix sort techniques as implemented by Edward Kmett in the discrimination package.
While there's a great deal going on there, it largely focuses around a type like this
data Group a = Group (forall b . [(a, b)] -> [[b]])
If you have a value of type Group a you essentially must have an equivalence relationship on a because if I give you an association between as and some type b completely unknown to you then you can give me "groupings" of b.
groupId :: Group a -> [a] -> [[a]]
groupId (Group grouper) = grouper . map (\a -> (a, a))
You can see this as a core type for writing a utility library of groupings. For instance, we might want to know that if we can Group a and Group b then we can Group (a, b) (more on this in a second). Henglein's core idea is that if you can start with some basic Groups on integers—we can write very fast Group Int32 implementations via radix sort—and then use combinators to extend them over all types then you will have generalized radix sort to algebraic data types.
So how might we build our combinator library?
Well, f :: Group a -> Group b -> Group (a, b) is pretty important in that it lets us make groups of product-like types. Normally, we'd get this from Applicative and liftA2 but Group, you'll notice, is Contravaiant, not a Functor.
So instead we use Divisible
divided :: Group a -> Group b -> Group (a, b)
Notice that this arises in a strange way from
divide :: (a -> (b, c)) -> Group b -> Group c -> Group a
as it has the typical "reversed arrow" character of contravariant things. We can now understand things like divide and conquer in terms of their interpretation on Group.
Divide says that if I want to build a strategy for equating as using strategies for equating bs and cs, I can do the following for any type x
Take your partial relation [(a, x)] and map over it with a function f :: a -> (b, c), and a little tuple manipulation, to get a new relation [(b, (c, x))].
Use my Group b to discriminate [(b, (c, x))] into [[(c, x)]]
Use my Group c to discriminate each [(c, x)] into [[x]] giving me [[[x]]]
Flatten the inner layers to get [[x]] like we need
instance Divisible Group where
conquer = Group $ return . fmap snd
divide k (Group l) (Group r) = Group $ \xs ->
-- a bit more cleverly done here...
l [ (b, (c, d)) | (a,d) <- xs, let (b, c) = k a] >>= r
We also get interpretations of the more tricky Decidable refinement of Divisible
class Divisible f => Decidable f where
lose :: (a -> Void) -> f a
choose :: (a -> Either b c) -> f b -> f c -> f a
instance Decidable Group where
lose :: (a -> Void) -> Group a
choose :: (a -> Either b c) -> Group b -> Group c -> Group a
These read as saying that for any type a of which we can guarantee there are no values (we cannot produce values of Void by any means, a function a -> Void is a means of producing Void given a, thus we must not be able to produce values of a by any means either!) then we immediately get a grouping of zero values
lose _ = Group (\_ -> [])
We also can go a similar game as to divide above except instead of sequencing our use of the input discriminators, we alternate.
Using these techniques we build up a library of "Groupable" things, namely Grouping
class Grouping a where
grouping :: Group a
and note that nearly all the definitions arise from the basic definition atop groupingNat which uses fast monadic vector manipuations to achieve an efficient radix sort.

Haskell: Filtering based on an index vector, using only basic higher-order functions

The problem
I have a vector a of size N holding sample data, and another vector b of size M (N>M) holding indices. I would like to obtain a vector c of size N containing the filtered elements from a based on the indices in b.
The question
Is it possible to implement the desired function without using list comprehension, just basic higher-order functions like map, zipWith, filter, etc. (more precisely, their equivalents mapV, zipWithV, filterV, etc.)
Prerequisites:
I am using a Haskell Embedded Domain Specific Language (ForSyDe, module ForSyDe.Shallow.Vector), limited to a set of hardware synthesize-able functions. In order to respect the design methodology, I am allowed to use only the provided functions (thus I cannot use list comprehensions, etc.)
Disclaimer:
I did not test this code for functionality because cabal started bugging around. It worked well for lists and as I transformed every vector to a list, it should work fine although problems may arise.
Try this:
indexFilter :: (Num b, Eq b, Enum b) => Vector a -> Vector b -> Vector a
indexFilter vector indices = vector (map fst (filter (\x -> (snd x) `elem` (fromVector indices)) vectorMap))
where
vectorMap = zip (fromVector vector) [0..]
indexFilter takes a list of tuple of the form (<element>, <index>) and then returns a vector of all elements which index is in the vector b. vectorMap is a just a zip of the elements of a and their indices in the vector.
Although the answer provided by ThreeFx is a correct answer to the question, it did not solve my problem due to several constraints enforced by the design methodology (ForSyDe), which were not mentioned:
lists cannot be used (they cannot be synthesized to other backends). ForSyDe provides two data containers: Signal (for temporal span) and Vector (for spatial span). This should ensure analyzability for system synthesis.
elem does not have a ForSyDe.Shallow.Vector implementation
Solution 1
Using only what the library provides, the shortest solution I found is:
indexFilter1 :: (Num b, Eq b, Enum b) => Vector a
-> Vector b
-> Vector (Vector a)
indexFilter1 v = mapV (\idx -> selectV idx 1 1 v)
The output vector can further be unwrapped, depending on the further usage.
Solution 2
Translating ThreeFx's solution to satisfy the constraints mentioned:
indexFilter :: (Num b, Eq b, Enum b) => Vector a
-> Vector b
-> Vector a
indexFilter v idx = mapV (fst) (filterV (\x -> elemV (snd x) idx) vectorMap)
where
vectorMap = zipWithV (\a b -> (b, a)) (iterateV size (+1) 0) v
size = lengthV v
elemV a = foldlV (\acc x -> if x == a then True else acc) False

How can a function be "transparently augmented" in Haskell?

Situation
I have function f, which I want to augment with function g, resulting in function named h.
Definitions
By "augment", in the general case, I mean: transform either input (one or more arguments) or output (return value) of function f.
By "augment", in the specific case, (specific to my current situation) I mean: transform only the output (return value) of function f while leaving all the arguments intact.
By "transparent", in the context of "augmentation", (both the general case and the specific case) I mean: To couple g's implementation as loosely to f's implementation as possible.
Specific case
In my current situation, this is what I need to do:
h a b c = g $ f a b c
I am interested in rewriting it to something like this:
h = g . f -- Doesn't type-check.
Because from the perspective of h and g, it doesn't matter what arguments f take, they only care about the return value, hence it would be tight coupling to mention the arguments in any way. For instance, if f's argument count changes in the future, h will also need to be changed.
So far
I asked lambdabot on the #haskell IRC channel: #pl h a b c = g $ f a b c to which I got the response:
h = ((g .) .) . f
Which is still not good enough since the number of (.)'s is dependent on the number of f's arguments.
General case
I haven't done much research in this direction, but erisco on #haskell pointed me towards http://matt.immute.net/content/pointless-fun which hints to me that a solution for the general case could be possible.
So far
Using the functions defined by Luke Palmer in the above article this seems to be an equivalent of what we have discussed so far:
h = f $. id ~> id ~> id ~> g
However, it seems that this method sadly also suffers from being dependent on the number of arguments of f if we want to transform the return value of f -- just as the previous methods.
Working example
In JavaScript, for instance, it is possible to achieve transparent augmentation like this:
function h () { return g(f.apply(this, arguments)) }
Question
How can a function be "transparently augmented" in Haskell?
I am mainly interested in the specific case, but it would be also nice to know how to handle the general case.
You can sort-of do it, but since there is no way to specify a behavior for everything that isn't a function, you'll need a lot of trivial instances for all the other types you care about.
{-# LANGUAGE TypeFamilies, DefaultSignatures #-}
class Augment a where
type Result a
type Result a = a
type Augmented a r
type Augmented a r = r
augment :: (Result a -> r) -> a -> Augmented a r
default augment :: (a -> r) -> a -> r
augment g x = g x
instance Augment b => Augment (a -> b) where
type Result (a -> b) = Result b
type Augmented (a -> b) r = a -> Augmented b r
augment g f x = augment g (f x)
instance Augment Bool
instance Augment Char
instance Augment Integer
instance Augment [a]
-- and so on for every result type of every function you want to augment...
Example:
> let g n x ys = replicate n x ++ ys
> g 2 'a' "bc"
"aabc"
> let g' = augment length g
> g' 2 'a' "bc"
4
> :t g
g :: Int -> a -> [a] -> [a]
> :t g'
g' :: Int -> a -> [a] -> Int
Well, technically, with just enough IncoherentInstances you can do pretty much anything:
{-# LANGUAGE MultiParamTypeClasses, TypeFamilies,
FlexibleInstances, UndecidableInstances, IncoherentInstances #-}
class Augment a b f h where
augment :: (a -> b) -> f -> h
instance (a ~ c, h ~ b) => Augment a b c h where
augment = ($)
instance (Augment a b d h', h ~ (c -> h')) => Augment a b (c -> d) h where
augment g f = augment g . f
-- Usage
t1 = augment not not
r1 = t1 True
t2 = augment (+1) (+)
r2 = t2 2 3
t3 = augment (+1) foldr
r3 = t3 (+) 0 [2,3]
The problem is that the real return value of something like a -> b -> c isn't
c, but b -> c. What you want require some kind of test that tells you if a type isn't
a function type. You could enumerate the types you are interested in, but that's not so
nice. I think HList solve this problem somehow, look at the paper. I managed to understand a bit of the solution with overlapping instances, but the rest goes a bit over my head I'm afraid.
JavaScript works, because its arguments are a sequence, or a list, so there is just one argument, really. In that sense it is the same as a curried version of the functions with a tuple representing the collection of arguments.
In a strongly typed language you need a lot more information to do that "transparently" for a function type - for example, dependent types can express this idea, but require the functions to be of specific types, not a arbitrary function type.
I think I saw a workaround in Haskell that can do this, too, but, again, that works only for specific types, which capture the arity of the function, not any function.

Resources