Skip to content

Instantly share code, notes, and snippets.

@ulidtko
Last active July 1, 2020 09:05
Show Gist options
  • Save ulidtko/a96f65e26c72e78f6422 to your computer and use it in GitHub Desktop.
Save ulidtko/a96f65e26c72e78f6422 to your computer and use it in GitHub Desktop.
anamorphism excercise
#!/usr/bin/env runghc
{-# LANGUAGE DeriveFunctor, DeriveFoldable #-}
{-# LANGUAGE ViewPatterns, LambdaCase #-}
{-# LANGUAGE Rank2Types #-}
module Main where
import Data.List (sort, elemIndices)
import qualified Data.Tree
import Control.Monad (guard)
{-- cabal install nondeterminism pretty-tree --}
import Control.Monad.Amb
import Data.Tree.Pretty
----------------------------------
-- http://pastebin.com/2yhjqBDq --
----------------------------------
type StrPair = (String, String)
datum1 :: StrPair
datum1 = ("hal@irdamE", "damEra@ilh")
datum2 :: StrPair
datum2 = ("er muyn oaia1e 9cbi14bdcc55d15b4227fb43f8l:9e8odc7dens 0eaPl s.em.iderotrr@t h.aus c ilaemo saeelP", ".o elPsaec lamei.a sur@h treotrdil0ems.al Pe7 dnse8dco9e:i438f7bfc5224b5d151bdc4ai bc91eamuoy ne r")
data TreeF a r = Leaf | Node r a r
deriving (Eq, Functor, Foldable)
type Tree a = Fix (TreeF a)
unfoldStep :: StrPair -> Amb' (TreeF Char StrPair)
unfoldStep ("", "") = pure Leaf
unfoldStep (lcr, crl) = do
let nodeC = head crl
nodeI <- amb $ elemIndices nodeC lcr
let (subleft, tail -> subright) = splitAt nodeI lcr
let (nleft, nright) = (length subleft, length subright)
let (crlSubR, crlSubL) = splitAt nright (tail crl)
guard $
sort subright == sort crlSubR
&&
sort subleft == sort crlSubL
return $ Node (subleft, crlSubL) nodeC (subright, crlSubR)
solve :: StrPair -> Either String (Tree Char)
solve (s1,s2) =
if (sort s1 == sort s2)
then Right . oneValue . anaM unfoldStep $ (s1,s2)
else Left "Invalid input"
pretty :: Tree Char -> String
pretty = drawVerticalTree . toDataTree
where
toDataTree = cata $ \case
Node l c r -> Data.Tree.Node ['[', c, ']'] (filter nonleaf [l, r])
Leaf -> Data.Tree.Node "Leaf" []
nonleaf (Data.Tree.Node "Leaf" _) = False
nonleaf _ = True
decoded :: Tree Char -> String
decoded = cata $ \case
Leaf -> ""
Node l c r -> concat [r, l, [c]]
-------------------------------------------------------------------------------
main :: IO ()
main = do
let solutions = allValues . anaM unfoldStep $ datum2
for (zip [1..] solutions) $ \(i, solution) -> do
putStrLn . unlines $
[ "== Solution " ++ show i ++ " =="
, pretty solution
, "Decoded string: " ++ decoded solution
, ""
]
for = flip mapM_
-------------------------------------------------------------------------------
-- What dark wizardry is this?! -- the unprepared reader.
-------------------------------------------------------------------------------
instance Traversable (TreeF a) where
traverse _ Leaf = pure Leaf
traverse g (Node l v r) = Node <$> g l <*> pure v <*> g r
anaM :: (Applicative m, Monad m, Traversable t)
=> (a -> m (t a)) -> (a -> m (Fix t))
anaM g = fmap Fix . (traverse (anaM g) =<<) . g
cata :: Functor f => (f a -> a) -> Fix f -> a
cata phi = phi . fmap (cata phi) . unfix
newtype Fix f = Fix { unfix :: f (Fix f) }
{- 27 Feb 2016 -}
== Solution 1 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------ ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------- ----------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ----------------- [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] -------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- [2] [e] [s] ---- [i] ---- [ ]
/ \ | / \ / \ |
[a] [b] ---- [P] [ ] [r] [t] [t]
| | / \
[i] ---- [4] [2]
| / \ |
[ ] [4] [d] [b]
| | |
---- [c] [5]
/ \ |
[1] [b] [d]
| | |
[e] [c] [1]
| |
[9] [5]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fb251d5b425cd4b9cbe1 ia1c74n your email.
== Solution 2 ==
[.]
|
-----------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------ ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------- ----------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ----------------- [8] --------- ------- --------- --------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] -------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- [2] [e] [s] ---- [d] [o] [t]
/ \ | / \ | |
[a] [b] ---- [P] [ ] [i] ----
| | / \ / \
[i] ---- [4] [2] [r] [t]
| / \ |
[ ] [4] [d] [b]
| | |
---- [c] [5]
/ \ |
[1] [b] [d]
| | |
[e] [c] [1]
| |
[9] [5]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fb251d5b425cd4b9cbe1 ia1c74n your email.
== Solution 3 ==
[.]
|
----------------------------------------------------------------------------
/ \
[l] [o]
| |
---------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------ --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------- -------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ----------------- [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] -------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- [2] [e] [s] ---- [i] ---- [ ]
/ \ | / \ / \ |
[a] [b] ---- [P] [ ] [r] [t] [t]
| | / \
[i] ---- [4] [2]
| / \ |
[ ] [4] [d] [b]
| | |
---- [c] [5]
/ \ |
[1] [b] [d]
| | |
[e] [c] [1]
| |
[9] [5]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fb251d5b425cd4b9cbe1 ia1c74n your email.
== Solution 4 ==
[.]
|
--------------------------------------------------------------------------
/ \
[l] [o]
| |
---------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------ --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------- -------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ----------------- [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] -------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- [2] [e] [s] ---- [d] [o] [t]
/ \ | / \ | |
[a] [b] ---- [P] [ ] [i] ----
| | / \ / \
[i] ---- [4] [2] [r] [t]
| / \ |
[ ] [4] [d] [b]
| | |
---- [c] [5]
/ \ |
[1] [b] [d]
| | |
[e] [c] [1]
| |
[9] [5]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fb251d5b425cd4b9cbe1 ia1c74n your email.
== Solution 5 ==
[.]
|
---------------------------------------------------------------------------------
/ \
[l] [o]
| |
-------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
--------------------------- ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ---------------------- ----------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ------------------- [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ----------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- [2] [e] [s] ---- [i] ---- [ ]
/ \ | / \ / \ |
[a] [b] ------- [P] [ ] [r] [t] [t]
| | / \
[i] ---- [4] [2]
| / \ |
[ ] [4] [d] [b]
| | |
---- [c] [5]
/ \ |
[1] [b] [d]
| | |
[e] [c] ----
| / \
[9] [5] [1]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fb215d5b425cd4b9cbe1 ia1c74n your email.
== Solution 6 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
-------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
--------------------------- ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ---------------------- ----------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ------------------- [8] --------- ------- --------- --------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ----------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- [2] [e] [s] ---- [d] [o] [t]
/ \ | / \ | |
[a] [b] ------- [P] [ ] [i] ----
| | / \ / \
[i] ---- [4] [2] [r] [t]
| / \ |
[ ] [4] [d] [b]
| | |
---- [c] [5]
/ \ |
[1] [b] [d]
| | |
[e] [c] ----
| / \
[9] [5] [1]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fb215d5b425cd4b9cbe1 ia1c74n your email.
== Solution 7 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
--------------------------- --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ---------------------- -------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ------------------- [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ----------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- [2] [e] [s] ---- [i] ---- [ ]
/ \ | / \ / \ |
[a] [b] ------- [P] [ ] [r] [t] [t]
| | / \
[i] ---- [4] [2]
| / \ |
[ ] [4] [d] [b]
| | |
---- [c] [5]
/ \ |
[1] [b] [d]
| | |
[e] [c] ----
| / \
[9] [5] [1]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fb215d5b425cd4b9cbe1 ia1c74n your email.
== Solution 8 ==
[.]
|
-----------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
--------------------------- --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ---------------------- -------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ------------------- [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ----------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- [2] [e] [s] ---- [d] [o] [t]
/ \ | / \ | |
[a] [b] ------- [P] [ ] [i] ----
| | / \ / \
[i] ---- [4] [2] [r] [t]
| / \ |
[ ] [4] [d] [b]
| | |
---- [c] [5]
/ \ |
[1] [b] [d]
| | |
[e] [c] ----
| / \
[9] [5] [1]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fb215d5b425cd4b9cbe1 ia1c74n your email.
== Solution 9 ==
[.]
|
----------------------------------------------------------------------------
/ \
[l] [o]
| |
--------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
---------------------- ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ----------------- ----------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] -------------- [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ------------ [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- [2] [e] [s] ---- [i] ---- [ ]
/ \ | / \ / \ |
[a] [b] [2] [P] [ ] [r] [t] [t]
| | |
[i] ---- [4]
| / \ |
[ ] [4] [d] [b]
| | |
---- [c] [5]
/ \ |
[1] [b] [d]
| | |
[e] [c] [1]
| |
[9] [5]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fb51d5b4225cd4b9cbe1 ia1c74n your email.
== Solution 10 ==
[.]
|
--------------------------------------------------------------------------
/ \
[l] [o]
| |
--------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
---------------------- ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ----------------- ----------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] -------------- [8] --------- ------- --------- --------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ------------ [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- [2] [e] [s] ---- [d] [o] [t]
/ \ | / \ | |
[a] [b] [2] [P] [ ] [i] ----
| | | / \
[i] ---- [4] [r] [t]
| / \ |
[ ] [4] [d] [b]
| | |
---- [c] [5]
/ \ |
[1] [b] [d]
| | |
[e] [c] [1]
| |
[9] [5]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fb51d5b4225cd4b9cbe1 ia1c74n your email.
== Solution 11 ==
[.]
|
--------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
---------------------- --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ----------------- -------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] -------------- [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ------------ [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- [2] [e] [s] ---- [i] ---- [ ]
/ \ | / \ / \ |
[a] [b] [2] [P] [ ] [r] [t] [t]
| | |
[i] ---- [4]
| / \ |
[ ] [4] [d] [b]
| | |
---- [c] [5]
/ \ |
[1] [b] [d]
| | |
[e] [c] [1]
| |
[9] [5]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fb51d5b4225cd4b9cbe1 ia1c74n your email.
== Solution 12 ==
[.]
|
------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
---------------------- --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ----------------- -------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] -------------- [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ------------ [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- [2] [e] [s] ---- [d] [o] [t]
/ \ | / \ | |
[a] [b] [2] [P] [ ] [i] ----
| | | / \
[i] ---- [4] [r] [t]
| / \ |
[ ] [4] [d] [b]
| | |
---- [c] [5]
/ \ |
[1] [b] [d]
| | |
[e] [c] [1]
| |
[9] [5]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fb51d5b4225cd4b9cbe1 ia1c74n your email.
== Solution 13 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------ ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------- ----------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ----------------- [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] -------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- [2] [e] [s] ---- [i] ---- [ ]
/ \ | / \ / \ |
[a] [b] [2] [P] [ ] [r] [t] [t]
| | |
[i] ---- [4]
| / \ |
[ ] [4] [d] [b]
| | |
---- [c] [5]
/ \ |
[1] [b] [d]
| | |
[e] [c] ----
| / \
[9] [5] [1]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fb15d5b4225cd4b9cbe1 ia1c74n your email.
== Solution 14 ==
[.]
|
-----------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------ ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------- ----------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ----------------- [8] --------- ------- --------- --------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] -------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- [2] [e] [s] ---- [d] [o] [t]
/ \ | / \ | |
[a] [b] [2] [P] [ ] [i] ----
| | | / \
[i] ---- [4] [r] [t]
| / \ |
[ ] [4] [d] [b]
| | |
---- [c] [5]
/ \ |
[1] [b] [d]
| | |
[e] [c] ----
| / \
[9] [5] [1]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fb15d5b4225cd4b9cbe1 ia1c74n your email.
== Solution 15 ==
[.]
|
----------------------------------------------------------------------------
/ \
[l] [o]
| |
---------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------ --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------- -------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ----------------- [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] -------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- [2] [e] [s] ---- [i] ---- [ ]
/ \ | / \ / \ |
[a] [b] [2] [P] [ ] [r] [t] [t]
| | |
[i] ---- [4]
| / \ |
[ ] [4] [d] [b]
| | |
---- [c] [5]
/ \ |
[1] [b] [d]
| | |
[e] [c] ----
| / \
[9] [5] [1]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fb15d5b4225cd4b9cbe1 ia1c74n your email.
== Solution 16 ==
[.]
|
--------------------------------------------------------------------------
/ \
[l] [o]
| |
---------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------ --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------- -------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ----------------- [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] -------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- [2] [e] [s] ---- [d] [o] [t]
/ \ | / \ | |
[a] [b] [2] [P] [ ] [i] ----
| | | / \
[i] ---- [4] [r] [t]
| / \ |
[ ] [4] [d] [b]
| | |
---- [c] [5]
/ \ |
[1] [b] [d]
| | |
[e] [c] ----
| / \
[9] [5] [1]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fb15d5b4225cd4b9cbe1 ia1c74n your email.
== Solution 17 ==
[.]
|
---------------------------------------------------------------------------------
/ \
[l] [o]
| |
-------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
--------------------------- ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ---------------------- ----------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ------------------- [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ----------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- ------ [e] [s] ---- [i] ---- [ ]
/ \ / \ / \ / \ |
[a] [b] [5] [2] [P] [ ] [r] [t] [t]
| | |
[i] ---- ----
| / \ / \
[ ] [4] [d] [4] [2]
| | |
---- [c] [b]
/ \ |
[1] [b] [5]
| | |
[e] [c] [d]
| |
[9] [1]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fb21d5b4255cd4b9cbe1 ia1c74n your email.
== Solution 18 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
-------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
--------------------------- ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ---------------------- ----------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ------------------- [8] --------- ------- --------- --------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ----------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- ------ [e] [s] ---- [d] [o] [t]
/ \ / \ / \ | |
[a] [b] [5] [2] [P] [ ] [i] ----
| | | / \
[i] ---- ---- [r] [t]
| / \ / \
[ ] [4] [d] [4] [2]
| | |
---- [c] [b]
/ \ |
[1] [b] [5]
| | |
[e] [c] [d]
| |
[9] [1]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fb21d5b4255cd4b9cbe1 ia1c74n your email.
== Solution 19 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
--------------------------- --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ---------------------- -------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ------------------- [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ----------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- ------ [e] [s] ---- [i] ---- [ ]
/ \ / \ / \ / \ |
[a] [b] [5] [2] [P] [ ] [r] [t] [t]
| | |
[i] ---- ----
| / \ / \
[ ] [4] [d] [4] [2]
| | |
---- [c] [b]
/ \ |
[1] [b] [5]
| | |
[e] [c] [d]
| |
[9] [1]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fb21d5b4255cd4b9cbe1 ia1c74n your email.
== Solution 20 ==
[.]
|
-----------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
--------------------------- --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ---------------------- -------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ------------------- [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ----------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- ------ [e] [s] ---- [d] [o] [t]
/ \ / \ / \ | |
[a] [b] [5] [2] [P] [ ] [i] ----
| | | / \
[i] ---- ---- [r] [t]
| / \ / \
[ ] [4] [d] [4] [2]
| | |
---- [c] [b]
/ \ |
[1] [b] [5]
| | |
[e] [c] [d]
| |
[9] [1]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fb21d5b4255cd4b9cbe1 ia1c74n your email.
== Solution 21 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------ ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------- ----------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ----------------- [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] -------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- ---- [e] [s] ---- [i] ---- [ ]
/ \ / \ / \ / \ |
[a] [b] [5] [2] [P] [ ] [r] [t] [t]
| | |
[i] ---- [2]
| / \ |
[ ] [4] [d] [4]
| | |
---- [c] [b]
/ \ |
[1] [b] [5]
| | |
[e] [c] [d]
| |
[9] [1]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fb1d5b42255cd4b9cbe1 ia1c74n your email.
== Solution 22 ==
[.]
|
-----------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------ ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------- ----------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ----------------- [8] --------- ------- --------- --------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] -------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- ---- [e] [s] ---- [d] [o] [t]
/ \ / \ / \ | |
[a] [b] [5] [2] [P] [ ] [i] ----
| | | / \
[i] ---- [2] [r] [t]
| / \ |
[ ] [4] [d] [4]
| | |
---- [c] [b]
/ \ |
[1] [b] [5]
| | |
[e] [c] [d]
| |
[9] [1]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fb1d5b42255cd4b9cbe1 ia1c74n your email.
== Solution 23 ==
[.]
|
----------------------------------------------------------------------------
/ \
[l] [o]
| |
---------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------ --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------- -------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ----------------- [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] -------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- ---- [e] [s] ---- [i] ---- [ ]
/ \ / \ / \ / \ |
[a] [b] [5] [2] [P] [ ] [r] [t] [t]
| | |
[i] ---- [2]
| / \ |
[ ] [4] [d] [4]
| | |
---- [c] [b]
/ \ |
[1] [b] [5]
| | |
[e] [c] [d]
| |
[9] [1]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fb1d5b42255cd4b9cbe1 ia1c74n your email.
== Solution 24 ==
[.]
|
--------------------------------------------------------------------------
/ \
[l] [o]
| |
---------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------ --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------- -------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ----------------- [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] -------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- ---- [e] [s] ---- [d] [o] [t]
/ \ / \ / \ | |
[a] [b] [5] [2] [P] [ ] [i] ----
| | | / \
[i] ---- [2] [r] [t]
| / \ |
[ ] [4] [d] [4]
| | |
---- [c] [b]
/ \ |
[1] [b] [5]
| | |
[e] [c] [d]
| |
[9] [1]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fb1d5b42255cd4b9cbe1 ia1c74n your email.
== Solution 25 ==
[.]
|
------------------------------------------------------------------------------------
/ \
[l] [o]
| |
----------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------------ ----------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ---------------------- [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ------------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- --------- [e] [s] ---- [i] ---- [ ]
/ \ / \ / \ / \ |
[a] [b] [5] [2] [P] [ ] [r] [t] [t]
| | | |
[i] ---- [d] ----
| / \ | / \
[ ] [4] [d] ---- [4] [2]
| | / \ |
---- [c] [5] [1] [b]
/ \
[1] [b]
| |
[e] [c]
|
[9]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fb2b4215d55cd4b9cbe1 ia1c74n your email.
== Solution 26 ==
[.]
|
----------------------------------------------------------------------------------
/ \
[l] [o]
| |
----------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------------ ----------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ---------------------- [8] --------- ------- --------- --------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ------------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- --------- [e] [s] ---- [d] [o] [t]
/ \ / \ / \ | |
[a] [b] [5] [2] [P] [ ] [i] ----
| | | | / \
[i] ---- [d] ---- [r] [t]
| / \ | / \
[ ] [4] [d] ---- [4] [2]
| | / \ |
---- [c] [5] [1] [b]
/ \
[1] [b]
| |
[e] [c]
|
[9]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fb2b4215d55cd4b9cbe1 ia1c74n your email.
== Solution 27 ==
[.]
|
---------------------------------------------------------------------------------
/ \
[l] [o]
| |
--------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------------ -------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ---------------------- [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ------------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- --------- [e] [s] ---- [i] ---- [ ]
/ \ / \ / \ / \ |
[a] [b] [5] [2] [P] [ ] [r] [t] [t]
| | | |
[i] ---- [d] ----
| / \ | / \
[ ] [4] [d] ---- [4] [2]
| | / \ |
---- [c] [5] [1] [b]
/ \
[1] [b]
| |
[e] [c]
|
[9]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fb2b4215d55cd4b9cbe1 ia1c74n your email.
== Solution 28 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
--------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------------ -------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ---------------------- [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ------------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- --------- [e] [s] ---- [d] [o] [t]
/ \ / \ / \ | |
[a] [b] [5] [2] [P] [ ] [i] ----
| | | | / \
[i] ---- [d] ---- [r] [t]
| / \ | / \
[ ] [4] [d] ---- [4] [2]
| | / \ |
---- [c] [5] [1] [b]
/ \
[1] [b]
| |
[e] [c]
|
[9]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fb2b4215d55cd4b9cbe1 ia1c74n your email.
== Solution 29 ==
[.]
|
---------------------------------------------------------------------------------
/ \
[l] [o]
| |
-------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
--------------------------- ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ---------------------- ----------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ------------------- [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ----------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- ------- [e] [s] ---- [i] ---- [ ]
/ \ / \ / \ / \ |
[a] [b] [5] [2] [P] [ ] [r] [t] [t]
| | | |
[i] ---- [d] [2]
| / \ | |
[ ] [4] [d] ---- [4]
| | / \ |
---- [c] [5] [1] [b]
/ \
[1] [b]
| |
[e] [c]
|
[9]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fbb42215d55cd4b9cbe1 ia1c74n your email.
== Solution 30 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
-------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
--------------------------- ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ---------------------- ----------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ------------------- [8] --------- ------- --------- --------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ----------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- ------- [e] [s] ---- [d] [o] [t]
/ \ / \ / \ | |
[a] [b] [5] [2] [P] [ ] [i] ----
| | | | / \
[i] ---- [d] [2] [r] [t]
| / \ | |
[ ] [4] [d] ---- [4]
| | / \ |
---- [c] [5] [1] [b]
/ \
[1] [b]
| |
[e] [c]
|
[9]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fbb42215d55cd4b9cbe1 ia1c74n your email.
== Solution 31 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
--------------------------- --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ---------------------- -------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ------------------- [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ----------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- ------- [e] [s] ---- [i] ---- [ ]
/ \ / \ / \ / \ |
[a] [b] [5] [2] [P] [ ] [r] [t] [t]
| | | |
[i] ---- [d] [2]
| / \ | |
[ ] [4] [d] ---- [4]
| | / \ |
---- [c] [5] [1] [b]
/ \
[1] [b]
| |
[e] [c]
|
[9]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fbb42215d55cd4b9cbe1 ia1c74n your email.
== Solution 32 ==
[.]
|
-----------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
--------------------------- --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ---------------------- -------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ------------------- [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ----------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- ------- [e] [s] ---- [d] [o] [t]
/ \ / \ / \ | |
[a] [b] [5] [2] [P] [ ] [i] ----
| | | | / \
[i] ---- [d] [2] [r] [t]
| / \ | |
[ ] [4] [d] ---- [4]
| | / \ |
---- [c] [5] [1] [b]
/ \
[1] [b]
| |
[e] [c]
|
[9]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fbb42215d55cd4b9cbe1 ia1c74n your email.
== Solution 33 ==
[.]
|
------------------------------------------------------------------------------------
/ \
[l] [o]
| |
----------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------------ ----------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ---------------------- [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ------------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- --------- [e] [s] ---- [i] ---- [ ]
/ \ / \ / \ / \ |
[a] [b] [5] [2] [P] [ ] [r] [t] [t]
| | | |
[i] ---- ---- ----
| / \ / \ / \
[ ] [4] [d] [5] [d] [4] [2]
| | | |
---- [c] [1] [b]
/ \
[1] [b]
| |
[e] [c]
|
[9]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fb2b421d555cd4b9cbe1 ia1c74n your email.
== Solution 34 ==
[.]
|
----------------------------------------------------------------------------------
/ \
[l] [o]
| |
----------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------------ ----------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ---------------------- [8] --------- ------- --------- --------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ------------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- --------- [e] [s] ---- [d] [o] [t]
/ \ / \ / \ | |
[a] [b] [5] [2] [P] [ ] [i] ----
| | | | / \
[i] ---- ---- ---- [r] [t]
| / \ / \ / \
[ ] [4] [d] [5] [d] [4] [2]
| | | |
---- [c] [1] [b]
/ \
[1] [b]
| |
[e] [c]
|
[9]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fb2b421d555cd4b9cbe1 ia1c74n your email.
== Solution 35 ==
[.]
|
---------------------------------------------------------------------------------
/ \
[l] [o]
| |
--------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------------ -------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ---------------------- [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ------------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- --------- [e] [s] ---- [i] ---- [ ]
/ \ / \ / \ / \ |
[a] [b] [5] [2] [P] [ ] [r] [t] [t]
| | | |
[i] ---- ---- ----
| / \ / \ / \
[ ] [4] [d] [5] [d] [4] [2]
| | | |
---- [c] [1] [b]
/ \
[1] [b]
| |
[e] [c]
|
[9]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fb2b421d555cd4b9cbe1 ia1c74n your email.
== Solution 36 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
--------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ------------------------ -------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ---------------------- [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ------------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- --------- [e] [s] ---- [d] [o] [t]
/ \ / \ / \ | |
[a] [b] [5] [2] [P] [ ] [i] ----
| | | | / \
[i] ---- ---- ---- [r] [t]
| / \ / \ / \
[ ] [4] [d] [5] [d] [4] [2]
| | | |
---- [c] [1] [b]
/ \
[1] [b]
| |
[e] [c]
|
[9]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fb2b421d555cd4b9cbe1 ia1c74n your email.
== Solution 37 ==
[.]
|
---------------------------------------------------------------------------------
/ \
[l] [o]
| |
-------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
--------------------------- ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ---------------------- ----------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ------------------- [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ----------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- ------- [e] [s] ---- [i] ---- [ ]
/ \ / \ / \ / \ |
[a] [b] [5] [2] [P] [ ] [r] [t] [t]
| | | |
[i] ---- ---- [2]
| / \ / \ |
[ ] [4] [d] [5] [d] [4]
| | | |
---- [c] [1] [b]
/ \
[1] [b]
| |
[e] [c]
|
[9]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fbb4221d555cd4b9cbe1 ia1c74n your email.
== Solution 38 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
-------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
--------------------------- ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ---------------------- ----------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ------------------- [8] --------- ------- --------- --------- [ ] [i] [a] [e]
| | / \ | / \ / \ / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ----------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- ------- [e] [s] ---- [d] [o] [t]
/ \ / \ / \ | |
[a] [b] [5] [2] [P] [ ] [i] ----
| | | | / \
[i] ---- ---- [2] [r] [t]
| / \ / \ |
[ ] [4] [d] [5] [d] [4]
| | | |
---- [c] [1] [b]
/ \
[1] [b]
| |
[e] [c]
|
[9]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fbb4221d555cd4b9cbe1 ia1c74n your email.
== Solution 39 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
--------------------------- --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ---------------------- -------------- ------------ -------------- [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ------------------- [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ----------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| / \ / \ / \ | / \ / \ / \
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| | | / \ | | | |
[n] --------- ------- [e] [s] ---- [i] ---- [ ]
/ \ / \ / \ / \ |
[a] [b] [5] [2] [P] [ ] [r] [t] [t]
| | | |
[i] ---- ---- [2]
| / \ / \ |
[ ] [4] [d] [5] [d] [4]
| | | |
---- [c] [1] [b]
/ \
[1] [b]
| |
[e] [c]
|
[9]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fbb4221d555cd4b9cbe1 ia1c74n your email.
== Solution 40 ==
[.]
|
-----------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
--------------------------- --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
[m] ---------------------- -------------- ------------ ------------ [l] [s] [l]
| / \ / \ / \ / \ | | |
---- [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
/ \ | | | | | | | / \ |
[e] [u] ------------------- [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
| | / \ | / \ | / \ / \ | |
[ ] [o] [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | | | | | | | | | | |
[r] [y] ----------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| / \ / \ / \ | / \ | |
[ ] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| | | / \ | / \ |
[n] --------- ------- [e] [s] ---- [d] [o] [t]
/ \ / \ / \ | |
[a] [b] [5] [2] [P] [ ] [i] ----
| | | | / \
[i] ---- ---- [2] [r] [t]
| / \ / \ |
[ ] [4] [d] [5] [d] [4]
| | | |
---- [c] [1] [b]
/ \
[1] [b]
| |
[e] [c]
|
[9]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fbb4221d555cd4b9cbe1 ia1c74n your email.
== Solution 41 ==
[.]
|
---------------------------------------------------------------------------------
/ \
[l] [o]
| |
-------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
-------------------------- ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ -------------- ----------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ------------ [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] --------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] [2] [e] [s] ---- [i] ---- [ ]
| | | / \ / \ |
[n] ---- ---- [P] [ ] [r] [t] [t]
/ \ / \
[4] [d] [4] [2]
| |
[c] [b]
|
[5]
|
[d]
|
[1]
|
[5]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fb251d5b425cd4b1c749cbea1 in your email.
== Solution 42 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
-------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
-------------------------- ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ -------------- ----------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ------------ [8] --------- ------- --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] --------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] [2] [e] [s] ---- [d] [o] [t]
| | | / \ | |
[n] ---- ---- [P] [ ] [i] ----
/ \ / \ / \
[4] [d] [4] [2] [r] [t]
| |
[c] [b]
|
[5]
|
[d]
|
[1]
|
[5]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fb251d5b425cd4b1c749cbea1 in your email.
== Solution 43 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
-------------------------- --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ -------------- -------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ------------ [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] --------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] [2] [e] [s] ---- [i] ---- [ ]
| | | / \ / \ |
[n] ---- ---- [P] [ ] [r] [t] [t]
/ \ / \
[4] [d] [4] [2]
| |
[c] [b]
|
[5]
|
[d]
|
[1]
|
[5]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fb251d5b425cd4b1c749cbea1 in your email.
== Solution 44 ==
[.]
|
-----------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
-------------------------- --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ -------------- -------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ------------ [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] --------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] [2] [e] [s] ---- [d] [o] [t]
| | | / \ | |
[n] ---- ---- [P] [ ] [i] ----
/ \ / \ / \
[4] [d] [4] [2] [r] [t]
| |
[c] [b]
|
[5]
|
[d]
|
[1]
|
[5]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fb251d5b425cd4b1c749cbea1 in your email.
== Solution 45 ==
[.]
|
------------------------------------------------------------------------------------
/ \
[l] [o]
| |
----------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ----------------- ----------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] -------------- [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------------ [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] [2] [e] [s] ---- [i] ---- [ ]
| | | / \ / \ |
[n] ---- ------- [P] [ ] [r] [t] [t]
/ \ / \
[4] [d] [4] [2]
| |
[c] [b]
|
[5]
|
[d]
|
----
/ \
[5] [1]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fb215d5b425cd4b1c749cbea1 in your email.
== Solution 46 ==
[.]
|
----------------------------------------------------------------------------------
/ \
[l] [o]
| |
----------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ----------------- ----------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] -------------- [8] --------- ------- --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------------ [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] [2] [e] [s] ---- [d] [o] [t]
| | | / \ | |
[n] ---- ------- [P] [ ] [i] ----
/ \ / \ / \
[4] [d] [4] [2] [r] [t]
| |
[c] [b]
|
[5]
|
[d]
|
----
/ \
[5] [1]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fb215d5b425cd4b1c749cbea1 in your email.
== Solution 47 ==
[.]
|
---------------------------------------------------------------------------------
/ \
[l] [o]
| |
--------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ----------------- -------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] -------------- [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------------ [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] [2] [e] [s] ---- [i] ---- [ ]
| | | / \ / \ |
[n] ---- ------- [P] [ ] [r] [t] [t]
/ \ / \
[4] [d] [4] [2]
| |
[c] [b]
|
[5]
|
[d]
|
----
/ \
[5] [1]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fb215d5b425cd4b1c749cbea1 in your email.
== Solution 48 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
--------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ----------------- -------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] -------------- [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------------ [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] [2] [e] [s] ---- [d] [o] [t]
| | | / \ | |
[n] ---- ------- [P] [ ] [i] ----
/ \ / \ / \
[4] [d] [4] [2] [r] [t]
| |
[c] [b]
|
[5]
|
[d]
|
----
/ \
[5] [1]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fb215d5b425cd4b1c749cbea1 in your email.
== Solution 49 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------ ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ------------ ----------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] --------- [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] [2] [e] [s] ---- [i] ---- [ ]
| | | / \ / \ |
[n] ---- [2] [P] [ ] [r] [t] [t]
/ \ |
[4] [d] [4]
| |
[c] [b]
|
[5]
|
[d]
|
[1]
|
[5]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fb51d5b4225cd4b1c749cbea1 in your email.
== Solution 50 ==
[.]
|
-----------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------ ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ------------ ----------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] --------- [8] --------- ------- --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] [2] [e] [s] ---- [d] [o] [t]
| | | / \ | |
[n] ---- [2] [P] [ ] [i] ----
/ \ | / \
[4] [d] [4] [r] [t]
| |
[c] [b]
|
[5]
|
[d]
|
[1]
|
[5]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fb51d5b4225cd4b1c749cbea1 in your email.
== Solution 51 ==
[.]
|
----------------------------------------------------------------------------
/ \
[l] [o]
| |
---------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------ --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ------------ -------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] --------- [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] [2] [e] [s] ---- [i] ---- [ ]
| | | / \ / \ |
[n] ---- [2] [P] [ ] [r] [t] [t]
/ \ |
[4] [d] [4]
| |
[c] [b]
|
[5]
|
[d]
|
[1]
|
[5]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fb51d5b4225cd4b1c749cbea1 in your email.
== Solution 52 ==
[.]
|
--------------------------------------------------------------------------
/ \
[l] [o]
| |
---------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------ --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ------------ -------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] --------- [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] [2] [e] [s] ---- [d] [o] [t]
| | | / \ | |
[n] ---- [2] [P] [ ] [i] ----
/ \ | / \
[4] [d] [4] [r] [t]
| |
[c] [b]
|
[5]
|
[d]
|
[1]
|
[5]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fb51d5b4225cd4b1c749cbea1 in your email.
== Solution 53 ==
[.]
|
---------------------------------------------------------------------------------
/ \
[l] [o]
| |
-------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
-------------------------- ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ -------------- ----------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ------------ [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] --------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] [2] [e] [s] ---- [i] ---- [ ]
| | | / \ / \ |
[n] ---- [2] [P] [ ] [r] [t] [t]
/ \ |
[4] [d] [4]
| |
[c] [b]
|
[5]
|
[d]
|
----
/ \
[5] [1]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fb15d5b4225cd4b1c749cbea1 in your email.
== Solution 54 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
-------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
-------------------------- ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ -------------- ----------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ------------ [8] --------- ------- --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] --------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] [2] [e] [s] ---- [d] [o] [t]
| | | / \ | |
[n] ---- [2] [P] [ ] [i] ----
/ \ | / \
[4] [d] [4] [r] [t]
| |
[c] [b]
|
[5]
|
[d]
|
----
/ \
[5] [1]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fb15d5b4225cd4b1c749cbea1 in your email.
== Solution 55 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
-------------------------- --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ -------------- -------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ------------ [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] --------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] [2] [e] [s] ---- [i] ---- [ ]
| | | / \ / \ |
[n] ---- [2] [P] [ ] [r] [t] [t]
/ \ |
[4] [d] [4]
| |
[c] [b]
|
[5]
|
[d]
|
----
/ \
[5] [1]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fb15d5b4225cd4b1c749cbea1 in your email.
== Solution 56 ==
[.]
|
-----------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
-------------------------- --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ -------------- -------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ------------ [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] --------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] [2] [e] [s] ---- [d] [o] [t]
| | | / \ | |
[n] ---- [2] [P] [ ] [i] ----
/ \ | / \
[4] [d] [4] [r] [t]
| |
[c] [b]
|
[5]
|
[d]
|
----
/ \
[5] [1]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fb15d5b4225cd4b1c749cbea1 in your email.
== Solution 57 ==
[.]
|
------------------------------------------------------------------------------------
/ \
[l] [o]
| |
----------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ----------------- ----------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] -------------- [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------------ [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] ------ [e] [s] ---- [i] ---- [ ]
| | / \ / \ / \ |
[n] ---- [5] [2] [P] [ ] [r] [t] [t]
/ \ |
[4] [d] ----
| / \
[c] [4] [2]
|
[b]
|
[5]
|
[d]
|
[1]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fb21d5b4255cd4b1c749cbea1 in your email.
== Solution 58 ==
[.]
|
----------------------------------------------------------------------------------
/ \
[l] [o]
| |
----------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ----------------- ----------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] -------------- [8] --------- ------- --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------------ [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] ------ [e] [s] ---- [d] [o] [t]
| | / \ / \ | |
[n] ---- [5] [2] [P] [ ] [i] ----
/ \ | / \
[4] [d] ---- [r] [t]
| / \
[c] [4] [2]
|
[b]
|
[5]
|
[d]
|
[1]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fb21d5b4255cd4b1c749cbea1 in your email.
== Solution 59 ==
[.]
|
---------------------------------------------------------------------------------
/ \
[l] [o]
| |
--------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ----------------- -------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] -------------- [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------------ [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] ------ [e] [s] ---- [i] ---- [ ]
| | / \ / \ / \ |
[n] ---- [5] [2] [P] [ ] [r] [t] [t]
/ \ |
[4] [d] ----
| / \
[c] [4] [2]
|
[b]
|
[5]
|
[d]
|
[1]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fb21d5b4255cd4b1c749cbea1 in your email.
== Solution 60 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
--------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ----------------- -------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] -------------- [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------------ [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] ------ [e] [s] ---- [d] [o] [t]
| | / \ / \ | |
[n] ---- [5] [2] [P] [ ] [i] ----
/ \ | / \
[4] [d] ---- [r] [t]
| / \
[c] [4] [2]
|
[b]
|
[5]
|
[d]
|
[1]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fb21d5b4255cd4b1c749cbea1 in your email.
== Solution 61 ==
[.]
|
---------------------------------------------------------------------------------
/ \
[l] [o]
| |
-------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
-------------------------- ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ -------------- ----------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ------------ [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] --------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] ---- [e] [s] ---- [i] ---- [ ]
| | / \ / \ / \ |
[n] ---- [5] [2] [P] [ ] [r] [t] [t]
/ \ |
[4] [d] [2]
| |
[c] [4]
|
[b]
|
[5]
|
[d]
|
[1]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fb1d5b42255cd4b1c749cbea1 in your email.
== Solution 62 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
-------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
-------------------------- ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ -------------- ----------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ------------ [8] --------- ------- --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] --------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] ---- [e] [s] ---- [d] [o] [t]
| | / \ / \ | |
[n] ---- [5] [2] [P] [ ] [i] ----
/ \ | / \
[4] [d] [2] [r] [t]
| |
[c] [4]
|
[b]
|
[5]
|
[d]
|
[1]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fb1d5b42255cd4b1c749cbea1 in your email.
== Solution 63 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
-------------------------- --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ -------------- -------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ------------ [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] --------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] ---- [e] [s] ---- [i] ---- [ ]
| | / \ / \ / \ |
[n] ---- [5] [2] [P] [ ] [r] [t] [t]
/ \ |
[4] [d] [2]
| |
[c] [4]
|
[b]
|
[5]
|
[d]
|
[1]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fb1d5b42255cd4b1c749cbea1 in your email.
== Solution 64 ==
[.]
|
-----------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------ ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
-------------------------- --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ -------------- -------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ------------ [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] --------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] ---- [e] [s] ---- [d] [o] [t]
| | / \ / \ | |
[n] ---- [5] [2] [P] [ ] [i] ----
/ \ | / \
[4] [d] [2] [r] [t]
| |
[c] [4]
|
[b]
|
[5]
|
[d]
|
[1]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fb1d5b42255cd4b1c749cbea1 in your email.
== Solution 65 ==
[.]
|
--------------------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------------- ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ------------------- ----------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ----------------- [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] -------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] --------- [e] [s] ---- [i] ---- [ ]
| | / \ / \ / \ |
[n] ---- [5] [2] [P] [ ] [r] [t] [t]
/ \ | |
[4] [d] [d] ----
| | / \
[c] ---- [4] [2]
/ \ |
[5] [1] [b]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fb2b4215d55cd4b1c749cbea1 in your email.
== Solution 66 ==
[.]
|
------------------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------------- ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ------------------- ----------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ----------------- [8] --------- ------- --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] -------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] --------- [e] [s] ---- [d] [o] [t]
| | / \ / \ | |
[n] ---- [5] [2] [P] [ ] [i] ----
/ \ | | / \
[4] [d] [d] ---- [r] [t]
| | / \
[c] ---- [4] [2]
/ \ |
[5] [1] [b]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fb2b4215d55cd4b1c749cbea1 in your email.
== Solution 67 ==
[.]
|
------------------------------------------------------------------------------------
/ \
[l] [o]
| |
----------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------------- --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ------------------- -------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ----------------- [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] -------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] --------- [e] [s] ---- [i] ---- [ ]
| | / \ / \ / \ |
[n] ---- [5] [2] [P] [ ] [r] [t] [t]
/ \ | |
[4] [d] [d] ----
| | / \
[c] ---- [4] [2]
/ \ |
[5] [1] [b]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fb2b4215d55cd4b1c749cbea1 in your email.
== Solution 68 ==
[.]
|
----------------------------------------------------------------------------------
/ \
[l] [o]
| |
----------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------------- --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ------------------- -------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ----------------- [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] -------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] --------- [e] [s] ---- [d] [o] [t]
| | / \ / \ | |
[n] ---- [5] [2] [P] [ ] [i] ----
/ \ | | / \
[4] [d] [d] ---- [r] [t]
| | / \
[c] ---- [4] [2]
/ \ |
[5] [1] [b]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fb2b4215d55cd4b1c749cbea1 in your email.
== Solution 69 ==
[.]
|
------------------------------------------------------------------------------------
/ \
[l] [o]
| |
----------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ----------------- ----------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] -------------- [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------------ [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] ------- [e] [s] ---- [i] ---- [ ]
| | / \ / \ / \ |
[n] ---- [5] [2] [P] [ ] [r] [t] [t]
/ \ | |
[4] [d] [d] [2]
| | |
[c] ---- [4]
/ \ |
[5] [1] [b]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fbb42215d55cd4b1c749cbea1 in your email.
== Solution 70 ==
[.]
|
----------------------------------------------------------------------------------
/ \
[l] [o]
| |
----------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ----------------- ----------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] -------------- [8] --------- ------- --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------------ [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] ------- [e] [s] ---- [d] [o] [t]
| | / \ / \ | |
[n] ---- [5] [2] [P] [ ] [i] ----
/ \ | | / \
[4] [d] [d] [2] [r] [t]
| | |
[c] ---- [4]
/ \ |
[5] [1] [b]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fbb42215d55cd4b1c749cbea1 in your email.
== Solution 71 ==
[.]
|
---------------------------------------------------------------------------------
/ \
[l] [o]
| |
--------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ----------------- -------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] -------------- [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------------ [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] ------- [e] [s] ---- [i] ---- [ ]
| | / \ / \ / \ |
[n] ---- [5] [2] [P] [ ] [r] [t] [t]
/ \ | |
[4] [d] [d] [2]
| | |
[c] ---- [4]
/ \ |
[5] [1] [b]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fbb42215d55cd4b1c749cbea1 in your email.
== Solution 72 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
--------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ----------------- -------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] -------------- [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------------ [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] ------- [e] [s] ---- [d] [o] [t]
| | / \ / \ | |
[n] ---- [5] [2] [P] [ ] [i] ----
/ \ | | / \
[4] [d] [d] [2] [r] [t]
| | |
[c] ---- [4]
/ \ |
[5] [1] [b]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fbb42215d55cd4b1c749cbea1 in your email.
== Solution 73 ==
[.]
|
--------------------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------------- ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ------------------- ----------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ----------------- [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] -------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] --------- [e] [s] ---- [i] ---- [ ]
| | / \ / \ / \ |
[n] ---- [5] [2] [P] [ ] [r] [t] [t]
/ \ | |
[4] [d] ---- ----
| / \ / \
[c] [5] [d] [4] [2]
| |
[1] [b]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fb2b421d555cd4b1c749cbea1 in your email.
== Solution 74 ==
[.]
|
------------------------------------------------------------------------------------
/ \
[l] [o]
| |
------------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------------- ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ------------------- ----------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ----------------- [8] --------- ------- --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] -------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] --------- [e] [s] ---- [d] [o] [t]
| | / \ / \ | |
[n] ---- [5] [2] [P] [ ] [i] ----
/ \ | | / \
[4] [d] ---- ---- [r] [t]
| / \ / \
[c] [5] [d] [4] [2]
| |
[1] [b]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fb2b421d555cd4b1c749cbea1 in your email.
== Solution 75 ==
[.]
|
------------------------------------------------------------------------------------
/ \
[l] [o]
| |
----------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------------- --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ------------------- -------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ----------------- [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] -------------- [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] --------- [e] [s] ---- [i] ---- [ ]
| | / \ / \ / \ |
[n] ---- [5] [2] [P] [ ] [r] [t] [t]
/ \ | |
[4] [d] ---- ----
| / \ / \
[c] [5] [d] [4] [2]
| |
[1] [b]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fb2b421d555cd4b1c749cbea1 in your email.
== Solution 76 ==
[.]
|
----------------------------------------------------------------------------------
/ \
[l] [o]
| |
----------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
------------------------------- --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ------------------- -------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] ----------------- [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] -------------- [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] --------- [e] [s] ---- [d] [o] [t]
| | / \ / \ | |
[n] ---- [5] [2] [P] [ ] [i] ----
/ \ | | / \
[4] [d] ---- ---- [r] [t]
| / \ / \
[c] [5] [d] [4] [2]
| |
[1] [b]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fb2b421d555cd4b1c749cbea1 in your email.
== Solution 77 ==
[.]
|
------------------------------------------------------------------------------------
/ \
[l] [o]
| |
----------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- ----------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ----------------- ----------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] -------------- [8] --------- ------- --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------------ [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] ------- [e] [s] ---- [i] ---- [ ]
| | / \ / \ / \ |
[n] ---- [5] [2] [P] [ ] [r] [t] [t]
/ \ | |
[4] [d] ---- [2]
| / \ |
[c] [5] [d] [4]
| |
[1] [b]
Decoded string: Please email us at hr@troider.com. Please send code:9870f83fbb4221d555cd4b1c749cbea1 in your email.
== Solution 78 ==
[.]
|
----------------------------------------------------------------------------------
/ \
[l] [o]
| |
----------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- ----------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ----------------- ----------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] -------------- [8] --------- ------- --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ / \ / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [ ] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------------ [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] ------- [e] [s] ---- [d] [o] [t]
| | / \ / \ | |
[n] ---- [5] [2] [P] [ ] [i] ----
/ \ | | / \
[4] [d] ---- [2] [r] [t]
| / \ |
[c] [5] [d] [4]
| |
[1] [b]
Decoded string: Please email us at h@troiderr.com. Please send code:9870f83fbb4221d555cd4b1c749cbea1 in your email.
== Solution 79 ==
[.]
|
---------------------------------------------------------------------------------
/ \
[l] [o]
| |
--------------------------------------------------------- ------------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- --------------------------- ------------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ----------------- -------------- ------------ -------------- [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] -------------- [8] --------- [ ] --------- ----------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [e] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------------ [f] ---- ---- [n] ------ ------ ---- [u] [e]
| | | | / \ / \ / \ | / \ / \ / \
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] [d] [o] [r] [h]
| / \ | | | / \ | | | |
[ ] [a] [e] [9] [b] ------- [e] [s] ---- [i] ---- [ ]
| | / \ / \ / \ |
[n] ---- [5] [2] [P] [ ] [r] [t] [t]
/ \ | |
[4] [d] ---- [2]
| / \ |
[c] [5] [d] [4]
| |
[1] [b]
Decoded string: Please email us at hr@troider.com. Pleasesend code:9870f83fbb4221d555cd4b1c749cbea1 in your email.
== Solution 80 ==
[.]
|
-------------------------------------------------------------------------------
/ \
[l] [o]
| |
--------------------------------------------------------- ---------------------
/ \ / \
[i] [0] [c] [ ]
| | | |
----------------------------- --------------------------- ---------------- [e]
/ \ / \ / \ |
[a] [4] [7] [e] [.] [ ] ----
| | | | | | / \
------------ ----------------- -------------- ------------ ------------ [l] [s] [l]
/ \ / \ / \ / \ / \ | | |
[m] [i] [7] [3] [8] [ ] [s] [m] [r] [a] ---- [a] [P]
| | | | | | | | | / \ |
---- [ ] -------------- [8] --------- [ ] --------- --------- [ ] [i] [a] [e]
/ \ | / \ | / \ | / \ / \ | |
[e] [u] ------- [c] [b] [f] [9] [d] [d] [a] [.] [r] [@] [s] [m]
| | / \ | | | | | | | | | |
[ ] [o] [1] [b] ------------ [f] ---- ---- [n] ------ [e] [h] [u] [e]
| | | | / \ / \ / \ | / \ | |
[r] [y] ---- [c] [1] [5] [:] [e] [o] [c] ---- [e] [l] ------ [ ]
| / \ | | | / \ | / \ |
[ ] [a] [e] [9] [b] ------- [e] [s] ---- [d] [o] [t]
| | / \ / \ | |
[n] ---- [5] [2] [P] [ ] [i] ----
/ \ | | / \
[4] [d] ---- [2] [r] [t]
| / \ |
[c] [5] [d] [4]
| |
[1] [b]
Decoded string: Please email us at h@troiderr.com. Pleasesend code:9870f83fbb4221d555cd4b1c749cbea1 in your email.
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment