Defining a High Order function that acesses data records - haskell

I pretend to create a high order function that uses as one of its parameters a function which belongs to the record of a certain Data Type.
For Example:
type Debt = Float
type Power = Int
Data State = S String Debt
Data City = C String Power Debt
Data Country = Country
{ states :: [State]
, cities :: [City] }
upDetail :: (Country -> [a])
-> ([a] -> b -> [a])
-> b -> Country -> Country
upDetail f g b country = country { f = new }
where old = f country
new = g old b
What the function above is supposed to do is pick an element of the record of the Country (with the function type Country -> [a]) and alter it according to a certain function type [a] -> b -> [a] and a certain b
However, when i try to compile this i get an error saying :
‘f’ is not a (visible) constructor field name
Is there any way i can overcome this problem? I thought of using Maybe Country as my result but i don't know how to do this.

As the comments mention, the normal solution to this is to use lenses:
upDetail :: Lens Country [a]
-> ([a] -> b -> [a])
-> b -> Country -> Country
upDetail f g b country = set f country new
where old = get f country
new = g old b
However, lenses aren't that hard to get a handle on, especially for so simple a purpose.
The simplest way of expressing a lens is as a getter and a setter function:
data Lens s a = Lens
{ get :: s -> a
, set :: s -> a -> s
}
_states :: Lens Country [State]
_states = Lens states $ \c new -> c { states = new }
_cities :: Lens Country [City]
_cities = Lens cities $ \c new -> c { cities = new }
This lets us modify the cities or states of a country pretty easily:
λ Country [] []
Country {states = [], cities = []}
λ upDetail _cities (\cs c -> c:cs) (C "Hereford" 100 3000) it
Country {states = [], cities = [C "Hereford" 100 3000.0]}
λ upDetail _states (\cs c -> c:cs) (S "Delmarva" 4) it
Country {states = [S "Delmarva" 4.0], cities = [C "Hereford" 100 3000.0]}
Lens get slightly more complex once you start thinking about composing lenses, which you're not getting into here, but you could.

Related

understanding cyclic/recursive data types in haskell

I'm trying to fully understand haskell's data types, so I created these:
data District = District {nameOfCity :: String,
subDistricts ::[DistrictUnit]}
deriving (Show, Eq)
data DistrictUnit = DistrictUnit District
| BranchUnit Branch
deriving (Show, Eq)
data Branch = Branch {nameOfBranch :: String,
numOfEmployees :: Int,
sales :: Int}
deriving (Show, Eq)
Here are some examples:
a = District {nameOfCity = "Berlin", subDistrcits = []}
b = District {nameOfCity = "New York",
subDistricts =
[DistrictUnit
(District {nameOfCity = "Amsterdam",
subDistricts =
[DistrictUnit
(District {nameOfCity = "London",
subDistricts = []})]})]}
c = District {nameOfCity = "Iowa" ,
subDistricts =
[BranchUnit
(Branch {nameOfBranch = "Omaha",
numOfEmployees = 3,
sales = 2343})]}
Now I'm trying to build two functions: getNameOfCity and getNameOfBranch:
getNameOfCity b -> ["New York", "Amsterdam", "London"]
But I have massive pattern matching issues. I just don't know how to build a function that works for all inputs.
Here are my attempts:
getNameOfCity :: District -> [String]
getNameOfCity (District a b) = [a]
This function will only give me the first name:
["New York"]
So I tried this:
getNameOfCity (District a [DistrictUnit (District b c)]) = [a, b]
And (of course) that one will only give me the first two names:
["New York", "Amsterdam"]
How can I make that getNameOfCity work for all inputs? And will getNamesOfBranch work the same way (since it has different parameters)? Thank you in advance :)
Rather than trying to do everything with a single function, it's easier to write separate helpers:
allDistrictNames :: District -> [String] -- This was your `getNameOfCity`
allDistrictNames_u :: DistrictUnit -> [String]
allDistrictNames_ul :: [DistrictUnit] -> [String]
allDistrictNames and allDistrictNames_u can now be implemented with simple pattern matches and calls to each other. allDistrictNames_ul needs to call allDistrictNames_u on all list elements, and combine the results. There's a standard function for this exact purpose.
You want getNameOfCity applied to a District to return its nameOfCity field, prepended to the list of city names from each of its subDistricts that are Districts and not Branches.
So you had a good starting point with something like this:
getNameOfCity :: District -> [String]
getNameOfCity (District name units) = [name]
But of course you need to do something with units. The pattern you wrote in your second example, [DistrictUnit (District b c)], only matches when the subDistricts field contains a list of exactly one element, where that element is also a DistrictUnit, and extracts only the nameOfCity field (b) from that district, ignoring any further nested subdistricts (in c).
To help you with this, I’m going to give you a template for you to fill in, following a common pattern that’s very helpful when you’re getting familiar with Haskell: working back from the desired result, breaking down the problem into small steps, and giving each step a name and a type signature. That way, if you make a mistake, the compiler will produce much more comprehensible error messages. Then, once you have a working solution, you can remove the intermediate variables and consolidate the steps into a more compact expression.
First, your desired result is the root district name prepended to the list of names of all subdistricts.
getNameOfCity :: District -> [String]
getNameOfCity (District name units) = let
allCities :: [String]
allCities = …
in name : allCities
To construct this, you’ll need to iterate over the units and extract the names from each district, then concatenate all the results.
getNameOfCity :: District -> [String]
getNameOfCity (District name units) = let
districtCities :: [[String]]
districtCities = … -- List of list of city names for each ‘District’
allCities :: [String]
allCities = … -- Concatenated ‘districtCities’
in name : allCities
The iteration over the units can be done in a few ways, but what I would do is extract only the Districts first so you have a narrower, more precise type to work with, and then you can simply apply getNameOfCity recursively on them.
getNameOfCity :: District -> [String]
getNameOfCity (District name units) = let
-- Extract only those ‘units’ that are ‘District’s
districts :: [District]
districts = …
-- Hint:
-- Hoogle ‘(a -> Maybe b) -> [a] -> [b]’
-- and define ‘getDistrict :: DistrictUnit -> Maybe District’;
-- or use a list comprehension of the form: ‘[… | … <- units]’
districtCities :: [[String]]
districtCities = …
allCities :: [String]
allCities = …
in name : allCities
You could follow a very similar approach for the branch names; it’s a good exercise to consider how you might abstract over the commonalities, once you have both of them in front of you.
It’s also a common higher-level approach to solve this sort of problem using the Semigroup & Monoid typeclasses, which are mathy names for the sets of types that can be “appended” associatively in some way (the <> operator), and have a default “empty” value (mempty) which is a no-op for appending. The general method is to map each value to a “summary” value—here, the list of city names—and then fold those summaries together, conveniently combined into a single operation called foldMap. For instance:
districtCities :: District -> [String]
districtCities (District city units) = [city] <> foldMap unitCities units
unitCities :: DistrictUnit -> [String]
-- Recursively summarise district.
unitCities (DistrictUnit district) = districtCities district
-- Return “empty” value for branch.
unitCities (BranchUnit branch) = mempty
This generalises to accumulating other fields, like the branch names:
districtBranches :: District -> [String]
districtBranches (District _ units) = foldMap unitBranches units
unitBranches :: DistrictUnit -> [String]
unitBranches (DistrictUnit district) = districtBranches district
unitBranches (BranchUnit branch) = [nameOfBranch branch]
Or other types of values, like the total sales, using the Sum monoid:
import Data.Monoid (Sum(..))
totalSales :: District -> Int
totalSales district = getSum (districtSales district)
-- Or: totalSales = getSum . districtSales
districtSales :: District -> Sum Int
districtSales (District _ units) = foldMap unitSales units
unitSales :: DistrictUnit -> Sum Int
unitSales (DistrictUnit district) = foldMap districtSales district
unitSales (BranchUnit branch) = Sum (branchSales branch)
Or even multiple values at once, using e.g.: (Sum 1, ["London"]) <> (Sum 2, ["Paris"]) = (Sum 3, ["London", "Paris"]). Notice how all these implementations have similar structure, too, though, and consider how you might abstract over this “folding” pattern generically.

data type with a default field and that needs a function that works with it

Say, I have a data type
data FooBar a = Foo String Char [a]
| Bar String Int [a]
I need to create values of this type and give empty list as the second field:
Foo "hello" 'a' []
or
Bar "world" 1 []
1) I do this everywhere in my code and I think it would be nice if I could omit the empty list part somehow and have the empty list assigned implicitly. Is this possible? Something similar to default function arguments in other languages.
2) Because of this [] "default" value, I often need to have a partial constructor application that results in a function that takes the first two values:
mkFoo x y = Foo x y []
mkBar x y = Bar x y []
Is there a "better" (more idiomatic, etc) way to do it? to avoid defining new functions?
3) I need a way to add things to the list:
add (Foo u v xs) x = Foo u v (x:xs)
add (Bar u v xs) x = Bar u v (x:xs)
Is this how it is done idiomatically? Just a general purpose function?
As you see I am a beginner, so maybe these questions make little sense. Hope not.
I'll address your questions one by one.
Default arguments do not exist in Haskell. They are simply not worth the added complexity and loss of compositionally. Being a functional language, you do a lot more function manipulation in Haskell, so funkiness like default arguments would be tough to handle.
One thing I didn't realize when I started Haskell is that data constructors are functions just like everything else. In your example,
Foo :: String -> Char -> [a] -> FooBar a
Thus you can write functions for filling in various arguments of other functions, and then those functions will work with Foo or Bar or whatever.
fill1 :: a -> (a -> b) -> b
fill1 a f = f a
--Note that fill1 = flip ($)
fill2 :: b -> (a -> b -> c) -> (a -> c)
--Equivalently, fill2 :: b -> (a -> b -> c) -> a -> c
fill2 b f = \a -> f a b
fill3 :: c -> (a -> b -> c -> d) -> (a -> b -> d)
fill3 c f = \a b -> f a b c
fill3Empty :: (a -> b -> [c] -> d) -> (a -> b -> d)
fill3Empty f = fill3 [] f
--Now, we can write
> fill3Empty Foo x y
Foo x y []
The lens package provides elegant solutions to questions like this. However, you can tell at a glance that this package is enormously complicated. Here is the net result of how you would call the lens package:
_list :: Lens (FooBar a) (FooBar b) [a] [b]
_list = lens getter setter
where getter (Foo _ _ as) = as
getter (Bar _ _ as) = as
setter (Foo s c _) bs = Foo s c bs
setter (Bar s i _) bs = Bar s i bs
Now we can do
> over _list (3:) (Foo "ab" 'c' [2,1])
Foo "ab" 'c' [3,2,1]
Some explanation: the lens function produces a Lens type when given a getter and a setter for some type. Lens s t a b is a type that says "s holds an a and t holds a b. Thus, if you give me a function a -> b, I can give you a function s -> t". That is exactly what over does: you provide it a lens and a function (in our case, (3:) was a function that adds 3 to the front of a List) and it applies the function "where the lens indicates". This is very similar to a functor, however, we have significantly more freedom (in this example, the functor instance would be obligated to change every element of the lists, not operate on the lists themselves).
Note that our new _list lens is very generic: it works equally well over Foo and Bar and the lens package provides many functions other than over for doing magical things.
The idiomatic thing is to take those parameters of a function or constructor that you commonly want to partially apply, and move them toward the beginning:
data FooBar a = Foo [a] String Char
| Bar [a] String Int
foo :: String -> Char -> FooBar a
foo = Foo []
bar :: String -> Int -> FooBar a
bar = Bar []
Similarly, reordering the parameters to add lets you partially apply add to get functions of type FooBar a -> FooBar a, which can be easily composed:
add :: a -> FooBar a -> FooBar a
add x (Foo xs u v) = Foo (x:xs) u v
add123 :: FooBar Int -> FooBar Int
add123 = add 1 . add 2 . add 3
add123 (foo "bar" 42) == Foo [1, 2, 3] "bar" 42
(2) and (3) are perfectly normal and idiomatic ways of doing such things. About (2) in particular, one expression you will occasionally hear is "smart constructor". That just means a function like your mkFoo/mkBar that produces a FooBar a (or a Maybe (FooBar a) etc.) with some extra logic to ensure only reasonable values can be constructed.
Here are some additional tricks that might (or might not!) make sense, depending on what you are trying to do with FooBar.
If you use Foo values and Barvalues in similar ways most of the time (i.e. the difference between having the Char field and the Int one is a minor detail), it makes sense to factor out the similarities and use a single constructor:
data FooBar a = FooBar String FooBarTag [a]
data FooBarTag = Foo Char | Bar Int
Beyond avoiding case analysis when you don't care about the FooBarTag, that allows you to safely use record syntax (records and types with multiple constructors do not mix well).
data FooBar a = FooBar
{ fooBarName :: String
, fooBarTag :: FooBarTag
, fooBarList :: [a]
}
Records allow you to use the fields without having to pattern match the whole thing.
If there are sensible defaults for all fields in a FooBar, you can go one step beyond mkFoo-like constructors and define a default value.
defaultFooBar :: FooBar a
defaultFooBar = FooBar
{ fooBarName = ""
, fooBarTag = Bar 0
, fooBarList = []
}
You don't need records to use a default, but they allow overriding default fields conveniently.
myFooBar = defaultFooBar
{ fooBarTag = Foo 'x'
}
If you ever get tired of typing long names for the defaults over and over, consider the data-default package:
instance Default (FooBar a) where
def = defaultFooBar
myFooBar = def { fooBarTag = Foo 'x' }
Do note that a significant number of people do not like the Default class, and not without reason. Still, for types which are very specific to your application (e.g. configuration settings) Default is perfectly fine IMO.
Finally, updating record fields can be messy. If you end up annoyed by that, you will find lens very useful. Note that it is a big library, and it might be a little overwhelming to a beginner, so take a deep breath beforehand. Here is a small sample:
{-# LANGUAGE TemplateHaskell #-} -- At the top of the file. Needed for makeLenses.
import Control.Lens
-- Note the underscores.
-- If you are going to use lenses, it is sensible not to export the field names.
data FooBar a = FooBar
{ _fooBarName :: String
, _fooBarTag :: FooBarTag
, _fooBarList :: [a]
}
makeLenses ''FooBar -- Defines lenses for the fields automatically.
defaultFooBar :: FooBar a
defaultFooBar = FooBar
{ _fooBarName = ""
, _fooBarTag = Bar 0
, _fooBarList = []
}
-- Using a lens (fooBarTag) to set a field without record syntax.
-- Note the lack of underscores in the name of the lens.
myFooBar = set fooBarTag (Foo 'x') defaultFooBar
-- Using a lens to access a field.
myTag = view fooBarTag myFooBar -- Results in Foo 'x'
-- Using a lens (fooBarList) to modify a field.
add :: a -> FooBar a -> FooBar a
add x fb = over fooBarList (x :) fb
-- set, view and over have operator equivalents, (.~). (^.) and (%~) respectively.
-- Note that (^.) is flipped with respect to view.
Here is a gentle introduction to lens which focuses on aspects I have not demonstrated here, specially in how nicely lenses can be composed.

basic haskell: error with simple function

I'm not sure what is wrong with my code, but when I try and run it I get
Couldn't match type `Integer' with `Int'
I'm using GHCi. I want to create a basic program that will go through the shop and give me all the customer names so I can then do a search to find out what item they have rented (a library). Is there a better way of getting the names?
This is my code:
type Name = String
type Customer = (Name,Int)
type shop = [Customer]
shop = [cust1, cust2]
cust1 = ("Neil", 311)
cust2 = ("Fred", 0)
getName :: (String,Int) -> Name
getName (a,b) = a
GHCi will default to using Integer over Int. You should specify the type of your tuples as cust1 = ("Neil", 311 :: Int) or cust2 = ("Fred", 0) :: (String, Int).
Edit after updates
If you already have Customer defined, you should write it as
cust1 = ("Neil", 311) :: Customer
cust2 = ("Fred", 0) :: Customer
getName :: Customer -> Name
getName (a, b) = a
You could also simplify things a bit by defining getName as
getName :: Customer -> Name
getName = fst
using ETA reduction and the built-in function fst

basic Haskell : list comprehension

Me again, I'm trying to iterate through my list of customers to find the correct customer and when I find them I want to display any non-zero int's that are attached to them. I'm not sure how to proceed. I know there will only be 1 record of the person's name in the shop.
type Name = String
type Customer = (Name,Int,Int)
type Shop = [Customer]
shop = [cust1, cust2]
cust1 = ("Steve", 321, 123) :: Customer
cust2 = ("John", 0,678) :: Customer
getName :: Customer -> Name
getName (a, b,c) = a
getNumbers :: Customer -> [Int]
getNumbers (a,b,c) = filter (/=0) [b,c]
rental:: Shop-> Name -> [Int]
rental shop' name' = map getNumbers [ x|x<-shop',getName x == name']
It is very useful to read error message!
test23.hs:10:9:
Couldn't match type `(Name, t0)' with `(Name, Int, Int)'
Expected type: Customer
Actual type: (Name, t0)
You have
getName (a, b) = a
but is defined
type Customer = (Name,Int,Int)
The right function looks like
getName (a, _, _) = a
After correct, you could see next meassage:
test23.hs:17:26:
Couldn't match type `[Int]' with `Int'
Expected type: Customer -> Int
Actual type: Customer -> [Int]
In the first argument of `map', namely `getNumbers'
...
In an equation for `rental'
But error is not in getNumbers, but in signature of rental:: Shop-> Name -> [Int]. Must be:
rental:: Shop-> Name -> [[Int]]
Your answer is pretty close. First of all, you need to update getName to take a 3-tuple, and second you should use concatMap getNumbers instead of map getNumbers.
Although, it looks like you're going to be adding new fields to your Customer type, so I would recommend that you switch to using a record instead:
data Customer = Customer
{ custName :: Name
, custVal1 :: Int -- I don't know what these are, so use real names
, custVal2 :: Int
} deriving (Eq, Show)
And now you could get rid of getName and do
getNumbers :: Customer -> [Int]
getNumbers c = filter (/= 0) [custVal1 c, custVal2 c]
rental :: Shop -> Name -> [Int]
rental shop' name' = concatMap getNumbers [x | x <- shop', custName x == name']
Now if you were to add another field to Customer, you don't have to update all your functions that don't depend on that field.

Different setter and getter types in Haskell's lenses

I've got a data type G, which have got field _repr :: Data.Graph.Inductive.Gr String String. The normal way, when adding new node into Gr graph, we have to provide an LNode a object, which basically is defined as a tuple of (Int, a), where Int is the nodes index in Graph - see the example function add below.
I want to implement a function addx, which will compute the index automatically (for example by using Data.Graph.Inductive.newNodes function). I want the addx to have signature of addx :: String -> G -> Int and this function will compute new free index, modify the graph G and return this computed index. Is it possible in Haskell to create such function (which will modify an existing object - G in this case) - by using lenses or something like that?
I have seen, that Haskell lens is defined like lens :: (a -> c) -> (a -> d -> b) -> Lens a b c d and lens is basically a "getter" and "setter", so its signature allows for different types of getter output (c), setter value (d) and setter output (b).
import qualified Data.Graph.Inductive as DG
data G = G { _repr :: DG.Gr String String, _name::String} deriving ( Show )
empty :: G
empty = G DG.empty ""
add :: DG.LNode String -> G -> G
add node g = g{_repr = DG.insNode node $ _repr g}
-- is it possible to define it?
addx :: String -> G -> Int
addx name g = undefined
main :: IO ()
main = do
let g = add (1, "test2")
$ add (0, "test1")
$ empty
n1 = addx "test2" g
g2 = DG.insEdge(n1,0)
$ DG.insEdge(0,1)
print $ g
Your type for addx is broken since you can't modify G in a pure function without returning the modified form like addx1 :: String -> G -> (Int, G). If you have a clever eye for Haskell monads, you might notice that this has an isomorphic type, addx2 :: String -> State G Int.
We can align everything to this "stateful" orientation
add' node = do g <- get
put $ g { _repr = DB.insNode node $ _repr g }
and make it more succinct with lenses
add'' node = repr %= DB.insNode node
The real challenge here is, at the end of the day, tracking the node identity. One way would be to carry it alongside the repr in your type
data G = G { _repr :: DG.Gr String String, _name :: String, _index :: Int }
empty = G DG.empty "" 0
then use that when building nodes (using lenses again!)
addx' name = do i <- use index
repr %= DB.insNode (i, node)
i += 1

Resources