printf a list of strings - haskell

I have the following code that is supposed to format a telephone number. (printf is from Text.Printf, splitPlaces is from Data.List.Split).
prettyPrint :: String -> String
prettyPrint phoneNumber = printf "(%s) %s-%s" part1 part2 part3
where [part1, part2, part3] = splitPlaces [3, 3, 4] phoneNumber
What I'm looking for is an operator that allows the following way of writing the function:
prettyPrint = printf "(%s) %s-%s" <operator> splitPlaces [3, 3, 4]
Does such an operator exist? Can it exist at all?

Assuming this operator should pop off elements from a list and pass them to a function one by one, no, that can't exist. Not really. It certainly is not a good idea. For this to work properly, you need to decide at runtime how many parameters to pass the function, a complete circumvention of the type system and all its benefits. You could say, lists are exactly here to properly state "I don't know how many elements there will be. printf itself rather violates much of Haskell's philosophy. The reason for its typeclass hackery of a variadic signature is not so much to allow a varying number of arguments, but arguments of different type, which is not relevant in your case.
What is easily implemented though is taking a fixed number of elements from the lists. Again not really a great idea because it's necessarily a partial function... but here goes:
pop3 :: (a -> a -> a -> b) -> [a] -> b
pop3 f [x,y,z] = f x y z
allowing you to write
printf "(%s) %s-%s" `pop3` splitPlaces [3, 3, 4] phoneNumber
Actually, we can generalise this: still fixed number at compile-time, but with a single name for any such number:
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
class YieldsEventually f a b where
popN :: f -> [a] -> b
instance YieldsEventually b a b where
popN = const
instance (YieldsEventually f a b) => YieldsEventually (a->f) a b where
popN f (x:xs) = popN (f x) xs
However, combining two functions that both require monomorphic arguments to resolve their own polymorphism-variadicity can't possibly work well, you need to fully qualify everything to make it compile:
(printf "(%s) %s-%s" :: String -> String -> String -> IO())
`popN` (splitPlaces [3, 3, 4] phoneNumber :: [String])
Not nice.
I think your original approach is the best; the explicit pattern also allows you to insert proper failure handling.
Finally, and obviously evilest, here is the dynamic-numbers-of-arguments solution:
{-# LANGUAGE RankNTypes #-}
popNPrintfr :: PrintfArg a => (forall p. PrintfType p => p) -> [a] -> IO ()
popNPrintfr printr [] = printr
popNPrintfr printr (x:xs) = popNPrintfr (printr x) xs
Again simpler to be used:
printf "(%s) %s-%s" `popNPrintfr` splitPlaces [3, 3, 4] phoneNumber

Related

Construct a dependent type out of a list in Haskell

I want to write a library in Haskell for Galois fields. A Galois field is defined by its irreducible polynomial. Galois field elements can only be added if they have the same Galois field. I want to lift the polynomial into the type of my Galois field, so that for example a Galois field with the polynomial [1, 2, 3] has a different type than a Galois Field with the polynomial [2, 0, 1]. This way i could assure that only Galois field elements with the same Galois field can be added. Is this possible?
My polynomial data type looks like this:
newtype Polynomial a = Polynomial [a]
My Galois field data type look like this:
data GF irr a = GF {
irreducible :: irr
, q :: PrimePower
}
So i want a constructor that takes a polynomial (for example (Polynomial [2, 0, 1])) and gives me a Galois field of the type GF (Polynomial Int) ([2, 0, 1]).
I know that [2, 0, 1] is not a valid type but i saw that with Data.Singletons it is possible to create types like
(SCons STrue (SCons SFalse SNil))
for [True, False], but i do not know how to construct types likes these from my list [2, 0, 1] and how the constructor would look like.
As Luke already commented, [2, 0, 1] is actually a valid type.
Prelude> :set -XDataKinds -XPolyKinds
Prelude> data A x = A deriving Show
Prelude> A :: A [2,0,1]
A
where the number literals are actually type-level Nat literals, and [...] is a lifted version of the list value-constructor to the type kind. This can be made explicit by writing it with “prime-quote syntax”
Prelude> A :: A '[2, 0, 1]
A
...so, this task is actually pretty trivial. You can just use
{-# LANGUAGE DataKinds, KindSignatures #-}
import GHC.TypeLits (Nat)
newtype Polynomial a = Polynomial [a]
data GF (irr :: Polynomial Nat) = GF {q :: PrimePower}
As also said by Luke, keep in mind though that type-level calculations don't work as well as they do in full dependently-typed languages. If you really want to do proof stuff with this, you should consider switching to Idris, Agda or Coq.
It seems that the "lifted" value will be used merely as a tag. For cases in which we only want it to work as a tag, but it's difficult to lift the required value to the type level with DataKinds, a possible alternative consists in attaching to the value a "ghostly" type tag conjured by means of a polymorphic incantation. Consider this helper module:
{-# LANGUAGE RankNTypes #-}
module Named (Named,forgetName,name) where
newtype Named n a = Named a -- don't export the constructor
forgetName :: Named n a -> a
forgetName (Named a) = a
name :: a -> ( forall name. Named name a -> r ) -> r
name x f = f ( Named x ) -- inside the callback, "x" has a "name" type tag attached
And this other module which depends on it:
module GF (Polynomial(..),GF,stuff,makeGF,addGF) where
import Named
newtype Polynomial a = Polynomial [a]
data GF a = GF { -- dont' export the constructor
_stuff :: Int -- don't export the bare field
}
stuff :: GF a -> Int
stuff (GF x) = x
makeGF :: Named ghost (Polynomial Int) -> Int -> GF ghost
makeGF _ = GF
addGF :: Named ghost (Polynomial Int) -> GF ghost -> GF ghost -> GF ghost
addGF _ x1 x2 = GF (stuff x1 + stuff x2)
I would be impossible for clients of this module to sum two GF values with different ghostly tags. Their only way of creating ghostly tags is through name, and they don't have the means of re-tagging either the Named values or the GF ones—we carefully hid constructors and bare fields to prevent that. So this would compile:
module Main where
import Named
import GF
main :: IO ()
main = print $
name (Polynomial [2::Int,3,4]) $ \ghost ->
let x1 = makeGF ghost 3
x2 = makeGF ghost 4
in stuff (addGF ghost x1 x2)
But this wouldn't:
main :: IO ()
main = print $
name (Polynomial [2::Int,3,4]) $ \ghost1 ->
name (Polynomial [3::Int]) $ \ghost2 ->
let x1 = makeGF ghost1 3
x2 = makeGF ghost2 4
in stuff (addGF ghost1 x1 x2)

Is it possible to compare operators like `(+), (-)` in haskell in the following way?

The elem command allows us to do the following:
elem 1 [1,2,3] = True
elem (Just 4) [(Just 5)] = False
My question is if this is possible to do on math operators.
For example:
elem (+) [(+), (-), div]
It does not seem like it is possible from definition of elem :: (Eq a, Foldable t) => a -> t a -> Bool, and (+) is of Num a => a -> a -> a.
Then how can one test this?
Yes, the universe package offers equality checking for total functions on finite domain -- at a price.
Data.Universe.Instances.Reverse Data.Word> elem (+) [(+), (-), (*) :: Word8 -> Word8 -> Word8]
True
Data.Universe.Instances.Reverse Data.Word> elem (+) [(-), (*) :: Word8 -> Word8 -> Word8]
False
What price? Comparison is done by applying the function to all possible inputs and comparing the corresponding outputs. In the case of Word8 there's only about ~60k inputs, so it's feasible to do it before you blink, but don't try that first one on Int -> Int -> Int...
In general, equality of functions is a big can of worms that you don't want to open. However, for numerical operators it is actually quite common to follow the symbolic-manipulation tradition of considering functions not so much as value mappings but as algebraic expressions, and those can in a naïve but not completely unreasonable way be compared efficiently. This requires a suitable symbolic “reflection type”; here with simple-reflect: you could do
{-# LANGUAGE FlexibleInstances #-}
import Debug.SimpleReflect
instance Eq (Expr -> Expr -> Expr) where
j == k = j magicL magicR == k magicL magicR
where magicL = 6837629875629876529923867
magicR = 9825763982763958726923876
main = print $ (+) `elem` [(+), (*), div :: Expr->Expr->Expr]
This is still a heuristic which might yield false positives, but it does work for your example and also for more involved ones. Note however that it does not consider arithmetic laws in any way, so it will give e.g. (+) /= flip (+).
I would recommend to try to solve your problem in a way that doesn't require equality of Haskell functions.

Getting all function arguments in haskel as list

Is there a way in haskell to get all function arguments as a list.
Let's supose we have the following program, where we want to add the two smaller numbers and then subtract the largest. Suppose, we can't change the function definition of foo :: Int -> Int -> Int -> Int. Is there a way to get all function arguments as a list, other than constructing a new list and add all arguments as an element of said list? More importantly, is there a general way of doing this independent of the number of arguments?
Example:
module Foo where
import Data.List
foo :: Int -> Int -> Int -> Int
foo a b c = result!!0 + result!!1 - result!!2 where result = sort ([a, b, c])
is there a general way of doing this independent of the number of arguments?
Not really; at least it's not worth it. First off, this entire idea isn't very useful because lists are homogeneous: all elements must have the same type, so it only works for the rather unusual special case of functions which only take arguments of a single type.
Even then, the problem is that “number of arguments” isn't really a sensible concept in Haskell, because as Willem Van Onsem commented, all functions really only have one argument (further arguments are actually only given to the result of the first application, which has again function type).
That said, at least for a single argument- and final-result type, it is quite easy to pack any number of arguments into a list:
{-# LANGUAGE FlexibleInstances #-}
class UsingList f where
usingList :: ([Int] -> Int) -> f
instance UsingList Int where
usingList f = f []
instance UsingList r => UsingList (Int -> r) where
usingList f a = usingList (f . (a:))
foo :: Int -> Int -> Int -> Int
foo = usingList $ (\[α,β,γ] -> α + β - γ) . sort
It's also possible to make this work for any type of the arguments, using type families or a multi-param type class. What's not so simple though is to write it once and for all with variable type of the final result. The reason being, that would also have to handle a function as the type of final result. But then, that could also be intepreted as “we still need to add one more argument to the list”!
With all respect, I would disagree with #leftaroundabout's answer above. Something being
unusual is not a reason to shun it as unworthy.
It is correct that you would not be able to define a polymorphic variadic list constructor
without type annotations. However, we're not usually dealing with Haskell 98, where type
annotations were never required. With Dependent Haskell just around the corner, some
familiarity with non-trivial type annotations is becoming vital.
So, let's take a shot at this, disregarding worthiness considerations.
One way to define a function that does not seem to admit a single type is to make it a method of a
suitably constructed class. Many a trick involving type classes were devised by cunning
Haskellers, starting at least as early as 15 years ago. Even if we don't understand their
type wizardry in all its depth, we may still try our hand with a similar approach.
Let us first try to obtain a method for summing any number of Integers. That means repeatedly
applying a function like (+), with a uniform type such as a -> a -> a. Here's one way to do
it:
class Eval a where
eval :: Integer -> a
instance (Eval a) => Eval (Integer -> a) where
eval i = \y -> eval (i + y)
instance Eval Integer where
eval i = i
And this is the extract from repl:
λ eval 1 2 3 :: Integer
6
Notice that we can't do without explicit type annotation, because the very idea of our approach is
that an expression eval x1 ... xn may either be a function that waits for yet another argument,
or a final value.
One generalization now is to actually make a list of values. The science tells us that
we may derive any monoid from a list. Indeed, insofar as sum is a monoid, we may turn arguments to
a list, then sum it and obtain the same result as above.
Here's how we can go about turning arguments of our method to a list:
class Eval a where
eval2 :: [Integer] -> Integer -> a
instance (Eval a) => Eval (Integer -> a) where
eval2 is i = \j -> eval2 (i:is) j
instance Eval [Integer] where
eval2 is i = i:is
This is how it would work:
λ eval2 [] 1 2 3 4 5 :: [Integer]
[5,4,3,2,1]
Unfortunately, we have to make eval binary, rather than unary, because it now has to compose two
different things: a (possibly empty) list of values and the next value to put in. Notice how it's
similar to the usual foldr:
λ foldr (:) [] [1,2,3,4,5]
[1,2,3,4,5]
The next generalization we'd like to have is allowing arbitrary types inside the list. It's a bit
tricky, as we have to make Eval a 2-parameter type class:
class Eval a i where
eval2 :: [i] -> i -> a
instance (Eval a i) => Eval (i -> a) i where
eval2 is i = \j -> eval2 (i:is) j
instance Eval [i] i where
eval2 is i = i:is
It works as the previous with Integers, but it can also carry any other type, even a function:
(I'm sorry for the messy example. I had to show a function somehow.)
λ ($ 10) <$> (eval2 [] (+1) (subtract 2) (*3) (^4) :: [Integer -> Integer])
[10000,30,8,11]
So far so good: we can convert any number of arguments into a list. However, it will be hard to
compose this function with the one that would do useful work with the resulting list, because
composition only admits unary functions − with some trickery, binary ones, but in no way the
variadic. Seems like we'll have to define our own way to compose functions. That's how I see it:
class Ap a i r where
apply :: ([i] -> r) -> [i] -> i -> a
apply', ($...) :: ([i] -> r) -> i -> a
($...) = apply'
instance Ap a i r => Ap (i -> a) i r where
apply f xs x = \y -> apply f (x:xs) y
apply' f x = \y -> apply f [x] y
instance Ap r i r where
apply f xs x = f $ x:xs
apply' f x = f [x]
Now we can write our desired function as an application of a list-admitting function to any number
of arguments:
foo' :: (Num r, Ord r, Ap a r r) => r -> a
foo' = (g $...)
where f = (\result -> (result !! 0) + (result !! 1) - (result !! 2))
g = f . sort
You'll still have to type annotate it at every call site, like this:
λ foo' 4 5 10 :: Integer
-1
− But so far, that's the best I can do.
The more I study Haskell, the more I am certain that nothing is impossible.

What's a better way of managing large Haskell records?

Replacing fields names with letters, I have cases like this:
data Foo = Foo { a :: Maybe ...
, b :: [...]
, c :: Maybe ...
, ... for a lot more fields ...
} deriving (Show, Eq, Ord)
instance Writer Foo where
write x = maybeWrite a ++
listWrite b ++
maybeWrite c ++
... for a lot more fields ...
parser = permute (Foo
<$?> (Nothing, Just `liftM` aParser)
<|?> ([], bParser)
<|?> (Nothing, Just `liftM` cParser)
... for a lot more fields ...
-- this is particularly hideous
foldl1 merge [foo1, foo2, ...]
merge (Foo a b c ...seriously a lot more...)
(Foo a' b' c' ...) =
Foo (max a a') (b ++ b') (max c c') ...
What techniques would allow me to better manage this growth?
In a perfect world a, b, and c would all be the same type so I could keep them in a list, but they can be many different types. I'm particularly interested in any way to fold the records without needing the massive patterns.
I'm using this large record to hold the different types resulting from permutation parsing the vCard format.
Update
I've implemented both the generics and the foldl approaches suggested below. They both work, and they both reduce three large field lists to one.
Datatype-generic programming techniques can be used to transform all the fields of a record in some "uniform" sort of way.
Perhaps all the fields in the record implement some typeclass that we want to use (the typical example is Show). Or perhaps we have another record of "similar" shape that contains functions, and we want to apply each function to the corresponding field of the original record.
For these kinds of uses, the generics-sop library is a good option. It expands the default Generics functionality of GHC with extra type-level machinery that provides analogues of functions like sequence or ap, but which work over all the fields of a record.
Using generics-sop, I tried to create a slightly less verbose version of your merge funtion. Some preliminary imports:
{-# language TypeOperators #-}
{-# language DeriveGeneric #-}
{-# language TypeFamilies #-}
{-# language DataKinds #-}
import Control.Applicative (liftA2)
import qualified GHC.Generics as GHC
import Generics.SOP
A helper function that lifts a binary operation to a form useable by the functions of generics-sop:
fn_2' :: (a -> a -> a) -> (I -.-> (I -.-> I)) a -- I is simply an Identity functor
fn_2' = fn_2 . liftA2
A general merge function that takes a vector of operators and works on any single-constructor record that derives Generic:
merge :: (Generic a, Code a ~ '[ xs ]) => NP (I -.-> (I -.-> I)) xs -> a -> a -> a
merge funcs reg1 reg2 =
case (from reg1, from reg2) of
(SOP (Z np1), SOP (Z np2)) ->
let npResult = funcs `hap` np1 `hap` np2
in to (SOP (Z npResult))
Code is a type family that returns a type-level list of lists describing the structure of a datatype. The outer list is for constructors, the inner lists contain the types of the fields for each constructor.
The Code a ~ '[ xs ] part of the constraint says "the datatype can only have one constructor" by requiring the outer list to have exactly one element.
The (SOP (Z _) pattern matches extract the (heterogeneus) vector of field values from the record's generic representation. SOP stands for "sum-of-products".
A concrete example:
data Person = Person
{
name :: String
, age :: Int
} deriving (Show,GHC.Generic)
instance Generic Person -- this Generic is from generics-sop
mergePerson :: Person -> Person -> Person
mergePerson = merge (fn_2' (++) :* fn_2' (+) :* Nil)
The Nil and :* constructors are used to build the vector of operators (the type is called NP, from n-ary product). If the vector doesn't match the number of fields in the record, the program won't compile.
Update. Given that the types in your record are highly uniform, an alternative way of creating the vector of operations is to define instances of an auxiliary typeclass for each field type, and then use the hcpure function:
class Mergeable a where
mergeFunc :: a -> a -> a
instance Mergeable String where
mergeFunc = (++)
instance Mergeable Int where
mergeFunc = (+)
mergePerson :: Person -> Person -> Person
mergePerson = merge (hcpure (Proxy :: Proxy Mergeable) (fn_2' mergeFunc))
The hcliftA2 function (that combines hcpure, fn_2 and hap) could be used to simplify things further.
Some suggestions:
(1) You can use the RecordWildCards extension to automatically
unpack a record into variables. Doesn't help if you need to unpack
two records of the same type, but it's a useful to keep in mind.
Oliver Charles has a nice blog post on it: (link)
(2) It appears your example application is performing a fold over the records.
Have a look at Gabriel Gonzalez's foldl package. There is also a blog post: (link)
Here is a example of how you might use it with a record like:
data Foo = Foo { _a :: Int, _b :: String }
The following code computes the maximum of the _a fields and the
concatenation of the _b_ fields.
import qualified Control.Foldl as L
import Data.Profunctor
data Foo = Foo { _a :: Int, _b :: String }
deriving (Show)
fold_a :: L.Fold Foo Int
fold_a = lmap _a (L.Fold max 0 id)
fold_b :: L.Fold Foo String
fold_b = lmap _b (L.Fold (++) "" id)
fold_foos :: L.Fold Foo Foo
fold_foos = Foo <$> fold_a <*> fold_b
theFoos = [ Foo 1 "a", Foo 3 "b", Foo 2 "c" ]
test = L.fold fold_foos theFoos
Note the use of the Profunctor function lmap to extract out
the fields we want to fold over. The expression:
L.Fold max 0 id
is a fold over a list of Ints (or any Num instance), and therefore:
lmap _a (L.Fold max 0 id)
is the same fold but over a list of Foo records where we use _a
to produce the Ints.

Sort by constructor ignoring (part of) value

Suppose I have
data Foo = A String Int | B Int
I want to take an xs :: [Foo] and sort it such that all the As are at the beginning, sorted by their strings, but with the ints in the order they appeared in the list, and then have all the Bs at the end, in the same order they appeared.
In particular, I want to create a new list containg the first A of each string and the first B.
I did this by defining a function taking Foos to (Int, String)s and using sortBy and groupBy.
Is there a cleaner way to do this? Preferably one that generalizes to at least 10 constructors.
Typeable, maybe? Something else that's nicer?
EDIT: This is used for processing a list of Foos that is used elsewhere. There is already an Ord instance which is the normal ordering.
You can use
sortBy (comparing foo)
where foo is a function that extracts the interesting parts into something comparable (e.g. Ints).
In the example, since you want the As sorted by their Strings, a mapping to Int with the desired properties would be too complicated, so we use a compound target type.
foo (A s _) = (0,s)
foo (B _) = (1,"")
would be a possible helper. This is more or less equivalent to Tikhon Jelvis' suggestion, but it leaves space for the natural Ord instance.
To make it easier to build comparison function for ADTs with large number of constructors, you can map values to their constructor index with SYB:
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Generics
data Foo = A String Int | B Int deriving (Show, Eq, Typeable, Data)
cIndex :: Data a => a -> Int
cIndex = constrIndex . toConstr
Example:
*Main Data.Generics> cIndex $ A "foo" 42
1
*Main Data.Generics> cIndex $ B 0
2
Edit:After re-reading your question, I think the best option is to make Foo an instance of Ord. I do not think there is any way to do this automatically that will act the way you want (just using deriving will create different behavior).
Once Foo is an instance of Ord, you can just use sort from Data.List.
In your exact example, you can do something like this:
data Foo = A String Int | B Int deriving (Eq)
instance Ord Foo where
(A _ _) <= (B _) = True
(A s _) <= (A s' _) = s <= s'
(B _) <= (B _) = True
When something is an instance of Ord, it means the data type has some ordering. Once we know how to order something, we can use a bunch of existing functions (like sort) on it and it will behave how you want. Anything in Ord has to be part of Eq, which is what the deriving (Eq) bit does automatically.
You can also derive Ord. However, the behavior will not be exactly what you want--it will order by all of the fields if it has to (e.g. it will put As with the same string in order by their integers).
Further edit: I was thinking about it some more and realized my solution is probably semantically wrong.
An Ord instance is a statement about your whole data type. For example, I'm saying that Bs are always equal with each other when the derived Eq instance says otherwise.
If the data your representing always behaves like this (that is, Bs are all equal and As with the same string are all equal) then an Ord instance makes sense. Otherwise, you should not actually do this.
However, you can do something almost exactly like this: write your own special compare function (Foo -> Foo -> Ordering) that encapsulates exactly what you want to do then use sortBy. This properly codifies that your particular sorting is special rather than the natural ordering of the data type.
You could use some template haskell to fill in the missing transitive cases. The mkTransitiveLt creates the transitive closure of the given cases (if you order them least to greatest). This gives you a working less-than, which can be turned into a function that returns an Ordering.
{-# LANGUAGE TemplateHaskell #-}
import MkTransitiveLt
import Data.List (sortBy)
data Foo = A String Int | B Int | C | D | E deriving(Show)
cmp a b = $(mkTransitiveLt [|
case (a, b) of
(A _ _, B _) -> True
(B _, C) -> True
(C, D) -> True
(D, E) -> True
(A s _, A s' _) -> s < s'
otherwise -> False|])
lt2Ord f a b =
case (f a b, f b a) of
(True, _) -> LT
(_, True) -> GT
otherwise -> EQ
main = print $ sortBy (lt2Ord cmp) [A "Z" 1, A "A" 1, B 1, A "A" 0, C]
Generates:
[A "A" 1,A "A" 0,A "Z" 1,B 1,C]
mkTransitiveLt must be defined in a separate module:
module MkTransitiveLt (mkTransitiveLt)
where
import Language.Haskell.TH
mkTransitiveLt :: ExpQ -> ExpQ
mkTransitiveLt eq = do
CaseE e ms <- eq
return . CaseE e . reverse . foldl go [] $ ms
where
go ms m#(Match (TupP [a, b]) body decls) = (m:ms) ++
[Match (TupP [x, b]) body decls | Match (TupP [x, y]) _ _ <- ms, y == a]
go ms m = m:ms

Resources