Making tree like data structures is relatively easy in Haskell. However, what if I want a structure like the following:
A (root)
/ \
B C
/ \ / \
D E F
So if I traverse down the structure through B to update E, the returned new updated structure also has E updated if I traverse through C.
Could someone give me some hints about how to achieve this? You can assume there are no loops.
I would flatten the data structure to an array, and operate on this instead:
import Data.Array
type Tree = Array Int -- Bounds should start at (1) and go to sum [1..n]
data TreeTraverse = TLeft TreeTraverse | TRight TreeTraverse | TStop
Given some traverse directions (left, right, stop), it's easy to see that if we go left, we simply add the current level to our position, and if we go right, we also add the current position plus one:
getPosition :: TreeTraverse -> Int
getPosition = getPosition' 1 1
where
getPosition' level pos (TLeft ts) = getPosition' (level+1) (pos+level) ts
getPosition' level pos (TRight ts) = getPosition' (level+1) (pos+level + 1) ts
getPosition' _ pos (TStop) = pos
In your case, you want to traverse either ABE or ACE:
traverseABE = TLeft $ TRight TStop
traverseACE = TRight $ TLeft TStop
Since we already now how to get the position of your element, and Data.Array provides some functions to set/get specific elements, we can use the following functions to get/set tree values:
getElem :: TreeTraverse -> Tree a -> a
getElem tt t = t ! getPosition tt
setElem :: TreeTraverse -> Tree a -> a -> Tree a
setElem tt t x = t // [(getPosition tt, x)]
To complete the code, lets use your example:
example = "ABCDEF"
exampleTree :: Tree Char
exampleTree = listArray (1, length example) example
And put everything to action:
main :: IO ()
main = do
putStrLn $ "Traversing from A -> B -> E: " ++ [getElem traverseABE exampleTree]
putStrLn $ "Traversing from A -> C -> E: " ++ [getElem traverseACE exampleTree]
putStrLn $ "exampleTree: " ++ show exampleTree ++ "\n"
putStrLn $ "Setting element from A -> B -> E to 'X', "
let newTree = setElem traverseABE exampleTree 'X'
putStrLn $ "but show via A -> C -> E: " ++ [getElem traverseACE newTree]
putStrLn $ "newTree: " ++ show newTree ++ "\n"
Note that this is most-likely not the best way to do this, but the first thing that I had in mind.
Once you've established identity, it can be done.
But first you must establish identity.
In many languages, values can be distinct from each other, but equal. In Python, for example:
>>> a = [1]
>>> b = [1]
>>> a == b
True
>>> a is b
False
You want to update E in one branch of the tree, and also update all other elements for which that element is E. But Haskell is referentially transparent: it has no notion of things being the same object; only equality, and even that is not applicable for every object.
One way you could do this is equality. Say this was your tree:
__A__
/ \
B C
/ \ / \
1 2 2 3
Then we could go through the tree and update all the 2s to, say, four. But this isn't exactly what you want in some cases.
In Haskell, if you want to update one thing in multiple places, you'll have to be explicit about what is and isn't the same thing. Another way you could deal with this is to tag each different value with a unique integer, and use that integer to determine identity:
____________A___________
/ \
B C
/ \ / \
(id=1)"foo" (id=2)"bar" (id=2)"bar" (id=3)"baz"
Then we could update all values with an identity of 2. Accidental collisions cannot be a problem, as there can be no collisions except those that are intentional.
This is essentially what STRef and IORef do, except they hoist the actual value into the monad's state and hide the identities from you. The only downside of using these is you'll need to make much of your code monadic, but you're probably not going to get away from that easily whatever you do. (Modifying values rather than replacing them is an inherently effectful thing to do.)
The structure you gave was not specified in much detail so it's impossible to tailor an example to your use case, but here's a simple example using the ST monad and a Tree:
import Control.Monad
import Control.Monad.ST
import Data.Tree
import Data.Traversable (traverse)
import Data.STRef
createInitialTree :: ST s (Tree (STRef s String))
createInitialTree = do
[a, b, c, d, e, f] <- mapM newSTRef ["A", "B", "C", "D", "E", "F"]
return $ Node a [ Node b [Node d [], Node e []]
, Node c [Node e [], Node f []]
]
dereferenceTree :: Tree (STRef s a) -> ST s (Tree a)
dereferenceTree = traverse readSTRef
test :: ST s (Tree String, Tree String)
test = do
tree <- createInitialTree
before <- dereferenceTree tree
let leftE = subForest (subForest tree !! 0) !! 1
writeSTRef (rootLabel leftE) "new" -- look ma, single update!
after <- dereferenceTree tree
return (before, after)
main = do
let (before, after) = runST test
putStrLn $ drawTree before
putStrLn $ drawTree after
Observe that although we only explicitly modified the value of the left E value, it changed on the right side, too, as desired.
I should note that these are not the only ways. There are probably many other solutions to this same problem, but they all require you to define identity sensibly. Only once that has been done can one begin the next step.
Related
i'm trying to write a function that for n gives matrix n*n with unique rows and columns (latin square).
I got function that gives my list of strings "1" .. "2" .. "n"
numSymbol:: Int -> [String]
I tried to generate all permutations of this, and them all n-length tuples of permutations, and them check if it is unique in row / columns. But complexity (n!)^2 works perfect for 2 and 3, but with n > 3 it takes forever. It is possible to build latin square from permutations directly, for example from
permutation ( numSymbol 3) = [["1","2","3"],["1","3","2"],["2","1","3"],["2","3","1"],["3","1","2"],["3","2","1"]]
get
[[["1","2","3",],["2","1","3"],["3","1","2"]] , ....]
without generating list like [["1",...],["1",...],...], when we know first element disqualify it ?
Note: since we can easily take a Latin square that's been filled with numbers from 1 to n and re-label it with anything we want, we can write code that uses integer symbols without giving anything away, so let's stick with that.
Anyway, the stateful backtracking/nondeterministic monad:
type StateList s = StateT s []
is helpful for this sort of problem.
Here's the idea. We know that every symbol s is going to appear exactly once in each row r, so we can represent this with an urn of all possible ordered pairs (r,s):
my_rs_urn = [(r,s) | r <- [1..n], s <- [1..n]]
Similarly, as every symbol s appears exactly once in each column c, we can use a second urn:
my_cs_urn = [(c,s) | c <- [1..n], s <- [1..n]]
Creating a Latin square is matter of filling in each position (r,c) with a symbol s by removing matching balls (r,s) and (c,s) (i.e., removing two balls, one from each urn) so that every ball is used exactly once. Our state will be the content of the urns.
We need backtracking because we might reach a point where for a particular position (r,c), there is no s such that (r,s) and (c,s) are both still available in their respective urns. Also, a pleasant side-effect of list-based backtracking/nondeterminism is that it'll generate all possible Latin squares, not just the first one it finds.
Given this, our state will look like:
type Urn = [(Int,Int)]
data S = S
{ size :: Int
, rs :: Urn
, cs :: Urn }
I've included the size in the state for convenience. It won't ever be modified, so it actually ought to be in a Reader instead, but this is simpler.
We'll represent a square by a list of cell contents in row-major order (i.e., the symbols in positions [(1,1),(1,2),...,(1,n),(2,1),...,(n,n)]):
data Square = Square
Int -- square size
[Int] -- symbols in row-major order
deriving (Show)
Now, the monadic action to generate latin squares will look like this:
type M = StateT S []
latin :: M Square
latin = do
n <- gets size
-- for each position (r,c), get a valid symbol `s`
cells <- forM (pairs n) (\(r,c) -> getS r c)
return $ Square n cells
pairs :: Int -> [(Int,Int)]
pairs n = -- same as [(x,y) | x <- [1..n], y <- [1..n]]
(,) <$> [1..n] <*> [1..n]
The worker function getS picks an s so that (r,s) and (c,s) are available in the respective urns, removing those pairs from the urns as a side effect. Note that getS is written non-deterministically, so it'll try every possible way of picking an s and associated balls from the urns:
getS :: Int -> Int -> M Int
getS r c = do
-- try each possible `s` in the row
s <- pickSFromRow r
-- can we put `s` in this column?
pickCS c s
-- if so, `s` is good
return s
Most of the work is done by the helpers pickSFromRow and pickCS. The first, pickSFromRow picks an s from the given row:
pickSFromRow :: Int -> M Int
pickSFromRow r = do
balls <- gets rs
-- "lift" here non-determinstically picks balls
((r',s), rest) <- lift $ choices balls
-- only consider balls in matching row
guard $ r == r'
-- remove the ball
modify (\st -> st { rs = rest })
-- return the candidate "s"
return s
It uses a choices helper which generates every possible way of pulling one element out of a list:
choices :: [a] -> [(a,[a])]
choices = init . (zipWith f <$> inits <*> tails)
where f a (x:b) = (x, a++b)
f _ _ = error "choices: internal error"
The second, pickCS checks if (c,s) is available in the cs urn, and removes it if it is:
pickCS :: Int -> Int -> M ()
pickCS c s = do
balls <- gets cs
-- only continue if the required ball is available
guard $ (c,s) `elem` balls
-- remove the ball
modify (\st -> st { cs = delete (c,s) balls })
With an appropriate driver for our monad:
runM :: Int -> M a -> [a]
runM n act = evalStateT act (S n p p)
where p = pairs n
this can generate all 12 Latin square of size 3:
λ> runM 3 latin
[Square 3 [1,2,3,2,3,1,3,1,2],Square 3 [1,2,3,3,1,2,2,3,1],...]
or the 576 Latin squares of size 4:
λ> length $ runM 4 latin
576
Compiled with -O2, it's fast enough to enumerate all 161280 squares of size 5 in a couple seconds:
main :: IO ()
main = print $ length $ runM 5 latin
The list-based urn representation above isn't very efficient. On the other hand, because the lengths of the lists are pretty small, there's not that much to be gained by finding more efficient representations.
Nonetheless, here's complete code that uses efficient Map/Set representations tailored to the way the rs and cs urns are used. Compiled with -O2, it runs in constant space. For n=6, it can process about 100000 Latin squares per second, but that still means it'll need to run for a few hours to enumerate all 800 million of them.
{-# OPTIONS_GHC -Wall #-}
module LatinAll where
import Control.Monad.State
import Data.List
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Map (Map, (!))
import qualified Data.Map as Map
data S = S
{ size :: Int
, rs :: Map Int [Int]
, cs :: Set (Int, Int) }
data Square = Square
Int -- square size
[Int] -- symbols in row-major order
deriving (Show)
type M = StateT S []
-- Get Latin squares
latin :: M Square
latin = do
n <- gets size
cells <- forM (pairs n) (\(r,c) -> getS r c)
return $ Square n cells
-- All locations in row-major order [(1,1),(1,2)..(n,n)]
pairs :: Int -> [(Int,Int)]
pairs n = (,) <$> [1..n] <*> [1..n]
-- Get a valid `s` for position `(r,c)`.
getS :: Int -> Int -> M Int
getS r c = do
s <- pickSFromRow r
pickCS c s
return s
-- Get an available `s` in row `r` from the `rs` urn.
pickSFromRow :: Int -> M Int
pickSFromRow r = do
urn <- gets rs
(s, rest) <- lift $ choices (urn ! r)
modify (\st -> st { rs = Map.insert r rest urn })
return s
-- Remove `(c,s)` from the `cs` urn.
pickCS :: Int -> Int -> M ()
pickCS c s = do
balls <- gets cs
guard $ (c,s) `Set.member` balls
modify (\st -> st { cs = Set.delete (c,s) balls })
-- Return all ways of removing one element from list.
choices :: [a] -> [(a,[a])]
choices = init . (zipWith f <$> inits <*> tails)
where f a (x:b) = (x, a++b)
f _ _ = error "choices: internal error"
-- Run an action in the M monad.
runM :: Int -> M a -> [a]
runM n act = evalStateT act (S n rs0 cs0)
where rs0 = Map.fromAscList $ zip [1..n] (repeat [1..n])
cs0 = Set.fromAscList $ pairs n
main :: IO ()
main = do
print $ runM 3 latin
print $ length (runM 4 latin)
print $ length (runM 5 latin)
Somewhat remarkably, modifying the program to produce only reduced Latin squares (i.e., with symbols [1..n] in order in both the first row and the first column) requires changing only two functions:
-- All locations in row-major order, skipping first row and column
-- i.e., [(2,2),(2,3)..(n,n)]
pairs :: Int -> [(Int,Int)]
pairs n = (,) <$> [2..n] <*> [2..n]
-- Run an action in the M monad.
runM :: Int -> M a -> [a]
runM n act = evalStateT act (S n rs0 cs0)
where -- skip balls [(1,1)..(n,n)] for first row
rs0 = Map.fromAscList $ map (\r -> (r, skip r)) [2..n]
-- skip balls [(1,1)..(n,n)] for first column
cs0 = Set.fromAscList $ [(c,s) | c <- [2..n], s <- skip c]
skip i = [1..(i-1)]++[(i+1)..n]
With these modifications, the resulting Square will include symbols in row-major order but skipping the first row and column. For example:
λ> runM 3 latin
[Square 3 [3,1,1,2]]
means:
1 2 3 fill in question marks 1 2 3
2 ? ? =====================> 2 3 1
3 ? ? in row-major order 3 1 2
This is fast enough to enumerate all 16,942,080 reduced Latin squares of size 7 in a few minutes:
$ stack ghc -- -O2 -main-is LatinReduced LatinReduced.hs && time ./LatinReduced
[1 of 1] Compiling LatinReduced ( LatinReduced.hs, LatinReduced.o )
Linking LatinReduced ...
16942080
real 3m9.342s
user 3m8.494s
sys 0m0.848s
readInts = fmap (map read.words) getLine
readInts :: IO [Int]
main = do
putStrLn "List number of A: "
num1 <- readInts
let a = [] ++ num1
putStrLn "List number of B: "
num2 <- readInts
let b = [] ++ num2
Choose some element a of A and some element b of B such that a + b doesn't belong to A and doesn't belong to B
Serious
If your instructor isn't teaching, and that isn't just you being burned out and stressed, then talk to the instructor. They probably aren't trying to waste your and their time. If that doesn't work then talk to the professor.
As for getting homework help here, it is entirely doable but help is very unlikely to appear without some semblance of an attempt and a clear cut issue. You usually need to come to the table with how the problem can be solved and have problems translating that how into the specifics of Haskell or whatever target language.
Cheeky
A cheeky response I'd use if I were in the classroom:
This is a finite domain so I'd just use DPLL. DPLL is a general purpose algorithm for finite domains that allows us to just state the problem as a symbolic computation and constraints then request satisfying models. We'll construct the problem first then use the SBV library to get the model.
Choose some element a of A
So lets define the set A (called as) as a list of symbolics and then constrain an existential to being a member of this set!
a <- exists "value1"
constrain (a `sElem` as)
and some element b of B
OK, same thing. We make a list of symbolic values and constrain an existential to being a member.
b <- exists "value2"
constrain (b `sElem` bs)
such that a + b
Let's define an alias for this:
let c = a + b
doesn't belong to A
We can just reuse the test for membership, sElem, and symbolic negation sNot.
constrain $ sNot (c `sElem` as)
and doesn't belong to B
Yep, same!
constrain $ sNot (c `sElem` bs)
Putting it together
Honestly the hardest part is actually running your problem more than stating it. We need to read the inputs (as you showed), call the solver (sat), and get the answer (aka the "model) via extractModel which can finally be printed.
#!/usr/bin/env cabal
{- cabal:
build-depends:
base, sbv >= 8.4
-}
{-# LANGUAGE ViewPatterns #-}
import Data.SBV
readInts :: IO [Int64]
readInts = fmap read . words <$> getLine
readInt :: IO Int64
readInt = read <$> getLine
main =
do putStrLn "List number of A: "
a <- readInts
putStrLn "List number of B: "
b <- readInts
result <- getValues a b
let values :: Maybe (Int64,Int64)
values = extractModel result
print values
getValues :: [Int64] -> [Int64] -> IO SatResult
getValues (map literal -> as) (map literal -> bs) = sat $
do a <- exists "value1"
constrain (a `sElem` as)
b <- exists "value2"
constrain (b `sElem` bs)
let c = a + b
constrain $ sNot (c `sElem` as)
constrain $ sNot (c `sElem` bs)
Because this uses SBV you'll have to have first installed z3. I included a cabal header to auto build as a package. For example:
brew install z3
...
chmod +x mycode.hs
./mycode.hs
...
List number of A:
1 3 4 5
List number of B:
1 2 3
Just (3,3)
I am trying to generate a tuple of Vectors by using a function that creates a custom data type (or a tuple) of values from an index. Here is an approach that achieves the desired result:
import Prelude hiding (map, unzip)
import Data.Vector hiding (map)
import Data.Array.Repa
import Data.Functor.Identity
data Foo = Foo {fooX :: Int, fooY :: Int}
unfoo :: Foo -> (Int, Int)
unfoo (Foo x y) = (x, y)
make :: Int -> (Int -> Foo) -> (Vector Int, Vector Int)
make n f = unzip $ generate n getElt where
getElt i = unfoo $ f i
Except that I would like to do it in a single iteration per Vector, almost like it is shown below, but avoiding multiple evaluation of function f:
make' :: Int -> (Int -> Foo) -> (Vector Int, Vector Int)
make' n f = (generate n getElt1, generate n getElt2) where
getElt1 i = fooX $ f i
getElt2 i = fooY $ f i
Just as a note, I understand that Vector library supports fusion, and the first example is already pretty efficient. I need a solution to generate concept, other libraries have very similar constructors (Repa has fromFunction for example), and I am using Vectors here simply to demonstrate a problem.
Maybe some sort of memoizing of f function call would work, but I cannot think of anything.
Edit:
Another demonstration of the problem using Repa:
makeR :: Int -> (Int -> Foo) -> (Array U DIM1 Int, Array U DIM1 Int)
makeR n f = runIdentity $ do
let arr = fromFunction (Z :. n) (\ (Z :. i) -> unfoo $ f i)
arr1 <- computeP $ map fst arr
arr2 <- computeP $ map snd arr
return (arr1, arr2)
Same as with vectors, fusion saves the day on performance, but an intermediate array arr of tuples is still required, which I am trying to avoid.
Edit 2: (3 years later)
In the Repa example above it will not create an intermediate array, since fromFunction creates a delayed array. Instead it will be even worse, it will evaluate f twice for each index, one for the first array, second time for the second array. Delayed array must be computed in order to avoid such duplication of work.
Looking back at my own question from a few years ago I can now easily show what I was trying to do back than and how to get it done.
In short, it can't be done purely, therefore we need to resort to ST monad and manual mutation of two vectors, but in the end we do get this nice and pure function that creates only two vectors and does not rely on fusion.
import Control.Monad.ST
import Data.Vector.Primitive
import Data.Vector.Primitive.Mutable
data Foo = Foo {fooX :: Int, fooY :: Int}
make :: Int -> (Int -> Foo) -> (Vector Int, Vector Int)
make n f = runST $ do
let n' = max 0 n
mv1 <- new n'
mv2 <- new n'
let fillVectors i
| i < n' = let Foo x y = f i
in write mv1 i x >> write mv2 i y >> fillVectors (i + 1)
| otherwise = return ()
fillVectors 0
v1 <- unsafeFreeze mv1
v2 <- unsafeFreeze mv2
return (v1, v2)
And the we use it in a similar fashion it is done with generate:
λ> make 10 (\ i -> Foo (i + i) (i * i))
([0,2,4,6,8,10,12,14,16,18],[0,1,4,9,16,25,36,49,64,81])
The essential thing you're trying to write is
splat f = unzip . fmap f
which shares the results of evaluating f between the two result vectors, but you want to avoid the intermediate vector. Unfortunately, I'm pretty sure you can't have it both ways in any meaningful sense. Consider a vector of length 1 for simplicity. In order for the result vectors to share the result of f (v ! 0), each will need a reference to a thunk representing that result. Well, that thunk has to be somewhere, and it really might as well be in a vector.
(Note: this post is a literate-haskell file. You can copy-paste it into a text
buffer, save it as someFile.lhs, and then run it using ghc.)
Problem description: I want ot create a graph with two different node types that
reference each other. The example below is very simplified. The two data types
A and B, are virtually identical here, but there's a reason for them to be
different in the original program.
We'll get the boring stuff out of the way.
> {-# LANGUAGE RecursiveDo, UnicodeSyntax #-}
>
> import qualified Data.HashMap.Lazy as M
> import Data.HashMap.Lazy (HashMap)
> import Control.Applicative ((<*>),(<$>),pure)
> import Data.Maybe (fromJust,catMaybes)
The data type definitions are themselves trivial:
> data A = A String B
> data B = B String A
In order to symbolize a difference between the two, we'll give them a different
Show instance.
> instance Show A where
> show (A a (B b _)) = a ++ ":" ++ b
>
> instance Show B where
> show (B b (A a _)) = b ++ "-" ++ a
And then tying the knot is of course trivial.
> knot ∷ (A,B)
> knot = let a = A "foo" b
> b = B "bar" a
> in (a,b)
This results in:
ghci> knot
(foo:bar,bar-foo)
That's exactly what I want!
Now the tricky part. I want to create this graph at runtime from user
input. This means I need error handling. Let's simulate some (valid but
nonsensical) user input:
> alist ∷ [(String,String)]
> alist = [("head","bot"),("tail","list")]
>
> blist ∷ [(String,String)]
> blist = [("bot","tail"),("list","head")]
(the user would of course not input these lists directly; the data would first
be massaged into this form)
It is trivial to do this without error handling:
> maps ∷ (HashMap String A, HashMap String B)
> maps = let aMap = M.fromList $ makeMap A bMap alist
> bMap = M.fromList $ makeMap B aMap blist
> in (aMap,bMap)
>
> makeMap ∷ (String → b → a) → HashMap String b
> → [(String,String)] → [(String,a)]
> makeMap _ _ [] = []
> makeMap c m ((a,b):xs) = (a,c a (fromJust $ M.lookup b m)):makeMap c m xs
This will obviously fail as soon as the input list of Strings references
something that isn't found in the respective maps. The "culprit" is fromJust;
we just assume that the keys will be there. Now, I could just ensure that the
user input is actually valid, and just use the above version. But this would
require two passes and wouldn't be very elegant, would it?
So I tried using the Maybe monad in a recursive do binding:
> makeMap' ∷ (String → b → a) → HashMap String b
> → [(String,String)] → Maybe (HashMap String a)
> makeMap' c m = maybe Nothing (Just . M.fromList) . go id
> where go l [] = Just (l [])
> go l ((a,b):xs) = maybe Nothing (\b' → go (l . ((a, c a b'):)) xs) $
> M.lookup b m
>
> maps' ∷ Maybe (HashMap String A, HashMap String B)
> maps' = do rec aMap ← makeMap' A bMap alist
> bMap ← makeMap' B aMap blist
> return (aMap, bMap)
But this ends up looping indefinitely: aMap needs bMap to be defined, and bMap
needs aMap. However, before I can even begin to access the keys in either map,
it needs to be fully evaluated, so that we know whether it is a Just or a
Nothing. The call to maybe in makeMap' is what bites me here, I think. It
contains a hidden case expression, and thus a refutable pattern.
The same would be true for Either so using some ErrorT transformer won't
help us here.
I don't want to fall back to run-time exceptions, as that would bounce me back
to the IO monad, and that would be admitting defeat.
The minimal modification to the above working example is to just remove
fromJust, and only take the results that actually work.
> maps'' ∷ (HashMap String A, HashMap String B)
> maps'' = let aMap = M.fromList . catMaybes $ makeMap'' A bMap alist
> bMap = M.fromList . catMaybes $ makeMap'' B aMap blist
> in (aMap, bMap)
>
> makeMap'' ∷ (String → b → a) → HashMap String b → [(String,String)] → [Maybe (String,a)]
> makeMap'' _ _ [] = []
> makeMap'' c m ((a,b):xs) = ((,) <$> pure a <*> (c <$> pure a <*> M.lookup b m))
> :makeMap'' c m xs
This doesn't work either, and, curiously, results in slightly different behaviour!
ghci> maps' -- no output
^CInterrupted.
ghci> maps'' -- actually finds out it wants to build a map, then stops.
(fromList ^CInterrupted
Using the debugger showed that these aren't even infinite loops (as I would have expected) but execution just stops. With maps' I get nothing, with the second attempt, I at least get to the first lookup, and then stall.
I'm stumped. In order to create the maps, I need to validate the input, but in order to validate it, I need to create the maps! The two obvious answers are: indirection, and pre-validation. Both of these are practical, if somewhat inelegant. I would like to know whether it is possible to do the error-catching in-line.
Is what I'm asking possible with Haskell's type system? (It
probably is, and I just can't find out how.) It is obviously possible by
percolating exceptions to the toplevel at fromJust, then catching them in IO, but that's not how I'd like to do it.
The problem is that when you tie the knot you don't "build" the structures of A and B but rather just declare how they are supposed to be built and then they get evaluated when needed. This naturally means that if the validation is done "in-line" with evaluation then the error checking must happen in IO because that's the only thing that can trigger evaluation (in your case, it's when you print the output of show).
Now, if you want to detect the error earlier you must declare the structure so that we can validate each node without traversing the whole infinite, cyclic structure. This solution is semantically the same as pre-validating the input, but hopefully you'll find it syntactically more elegant
import Data.Traversable (sequenceA)
maps' :: Maybe (HashMap String A, HashMap String B)
maps' =
let maMap = M.fromList $ map (makePair A mbMap) alist
mbMap = M.fromList $ map (makePair B maMap) blist
makePair c l (k,v) = (k, c k . fromJust <$> M.lookup v l)
in (,) <$> sequenceA maMap <*> sequenceA mbMap
This first defines the mutually recursive maps maMap and mbMap which have the types HashMap String (Maybe A) and HashMap String (Maybe B) respectively, meaning that they'll contain all the node keys but the keys are associated with Nothing if the node was invalid. The "cheating" happens in
c k . fromJust <$> M.lookup v l
This will essentially just look up the referenced node with M.lookup and if that succeeds we just assume that the returned node is valid and use fromJust. This prevents the infinite loop that would otherwise occur if we tried to validate the Maybe layers all the way down. If the lookup fails then this node is invalid i.e. Nothing.
Next we turn the HashMap String (Maybe a) maps "inside out" into Maybe (HashMap String a) maps using sequenceA from Data.Traversable. The resulting value is Just _ only if every node inside the map was Just _ and Nothing otherwise. This guarantees that the fromJust we used above cannot fail.
How do you increment a variable in a functional programming language?
For example, I want to do:
main :: IO ()
main = do
let i = 0
i = i + 1
print i
Expected output:
1
Simple way is to introduce shadowing of a variable name:
main :: IO () -- another way, simpler, specific to monads:
main = do main = do
let i = 0 let i = 0
let j = i i <- return (i+1)
let i = j+1 print i
print i -- because monadic bind is non-recursive
Prints 1.
Just writing let i = i+1 doesn't work because let in Haskell makes recursive definitions — it is actually Scheme's letrec. The i in the right-hand side of let i = i+1 refers to the i in its left hand side — not to the upper level i as might be intended. So we break that equation up by introducing another variable, j.
Another, simpler way is to use monadic bind, <- in the do-notation. This is possible because monadic bind is not recursive.
In both cases we introduce new variable under the same name, thus "shadowing" the old entity, i.e. making it no longer accessible.
How to "think functional"
One thing to understand here is that functional programming with pure — immutable — values (like we have in Haskell) forces us to make time explicit in our code.
In imperative setting time is implicit. We "change" our vars — but any change is sequential. We can never change what that var was a moment ago — only what it will be from now on.
In pure functional programming this is just made explicit. One of the simplest forms this can take is with using lists of values as records of sequential change in imperative programming. Even simpler is to use different variables altogether to represent different values of an entity at different points in time (cf. single assignment and static single assignment form, or SSA).
So instead of "changing" something that can't really be changed anyway, we make an augmented copy of it, and pass that around, using it in place of the old thing.
As a general rule, you don't (and you don't need to). However, in the interests of completeness.
import Data.IORef
main = do
i <- newIORef 0 -- new IORef i
modifyIORef i (+1) -- increase it by 1
readIORef i >>= print -- print it
However, any answer that says you need to use something like MVar, IORef, STRef etc. is wrong. There is a purely functional way to do this, which in this small rapidly written example doesn't really look very nice.
import Control.Monad.State
type Lens a b = ((a -> b -> a), (a -> b))
setL = fst
getL = snd
modifyL :: Lens a b -> a -> (b -> b) -> a
modifyL lens x f = setL lens x (f (getL lens x))
lensComp :: Lens b c -> Lens a b -> Lens a c
lensComp (set1, get1) (set2, get2) = -- Compose two lenses
(\s x -> set2 s (set1 (get2 s) x) -- Not needed here
, get1 . get2) -- But added for completeness
(+=) :: (Num b) => Lens a b -> Lens a b -> State a ()
x += y = do
s <- get
put (modifyL x s (+ (getL y s)))
swap :: Lens a b -> Lens a b -> State a ()
swap x y = do
s <- get
let x' = getL x s
let y' = getL y s
put (setL y (setL x s y') x')
nFibs :: Int -> Int
nFibs n = evalState (nFibs_ n) (0,1)
nFibs_ :: Int -> State (Int,Int) Int
nFibs_ 0 = fmap snd get -- The second Int is our result
nFibs_ n = do
x += y -- Add y to x
swap x y -- Swap them
nFibs_ (n-1) -- Repeat
where x = ((\(x,y) x' -> (x', y)), fst)
y = ((\(x,y) y' -> (x, y')), snd)
There are several solutions to translate imperative i=i+1 programming to functional programming. Recursive function solution is the recommended way in functional programming, creating a state is almost never what you want to do.
After a while you will learn that you can use [1..] if you need a index for example, but it takes a lot of time and practice to think functionally instead of imperatively.
Here's a other way to do something similar as i=i+1 not identical because there aren't any destructive updates. Note that the State monad example is just for illustration, you probably want [1..] instead:
module Count where
import Control.Monad.State
count :: Int -> Int
count c = c+1
count' :: State Int Int
count' = do
c <- get
put (c+1)
return (c+1)
main :: IO ()
main = do
-- purely functional, value-modifying (state-passing) way:
print $ count . count . count . count . count . count $ 0
-- purely functional, State Monad way
print $ (`evalState` 0) $ do {
count' ; count' ; count' ; count' ; count' ; count' }
Note: This is not an ideal answer but hey, sometimes it might be a little good to give anything at all.
A simple function to increase the variable would suffice.
For example:
incVal :: Integer -> Integer
incVal x = x + 1
main::IO()
main = do
let i = 1
print (incVal i)
Or even an anonymous function to do it.