Hello again,

without the --enable-timer option, I have managed to compile hugs. Nevertheless,
I was not successful with doc. OK, I don't care about it, but anyway...

I've run several tests. One of them is appended - for trial just type: cesty (1,1) /(It's a kind of state-space search implementation (horse problem) made by a student long
time ago, without any optimization, for testing very good.)/

 My older hugs interpreter stops with error: ERROR - Control stack overflow
GHCi stops with the same error: *** Exception: stack overflow
That's OK, really, that's correct behavior after printing some results.

Nevertheless, the new hugs compilation stops with this: Segmentation Fault(coredump) And that's probably not the correct end. May I do something wrong? I've thought that configure + make + make install_all_but_docs (no doc compiled) should work.

 Sorry for bothering if this is trivial or off topic.


 Regards, hoping for help,

   Dusan

--

Dusan Kolar            tel: +420 54 114 1238
UIFS FIT VUT Brno      fax: +420 54 114 1270
Bozetechova 2       e-mail: [EMAIL PROTECTED]
Brno 612 66
Czech Republic

--

---------------------------------------------------------------------
-- Bohuslav Krena (xkrena00)    2 IVT 23
-- FLP - Funkcionalni a logicke programovani
-- Project 1 - Kun na sachovnici
--
-- Zadani:
-- -------
-- Ze zadaneho pole najdete cestu tak, abyste prosli vsechna pole,
-- ale na zadne pole nesmite vstoupit dvakrat.
--
---------------------------------------------------------------------

type Pole = (Int,Int)
type Cesta = [Pole]

-- Test: z pole (1,1) - Pentium II Celeron 300 MHz.
--    1,2,3,4 ... < 1s
--    5 ...   2 s
--    6 ...  15 s
--    7 ... 240 s
--    30 ... do 30 minut neskoncil.
--    50, 60, 61 ... control stack overflow po nekolika vysledcich.
--    62, 65 ... control stack overflow ihned.
--
-- Vrati seznam vyhovujicich cest.
cesty :: Pole -> [Cesta]
cesty (s,r) 
       | pridej (s,r) [] == [] 
           = error "cesty: Zadane vychozi pole neni na sachovnici."
       | otherwise             = hledej [[(s,r)]]

-- Test: jako cesty.
-- Hleda mozne cesty.
hledej :: [Cesta] -> [Cesta]
hledej [] = []
hledej (xs:xss)
       | poli xs == 25 = xs : hledej xss
       | otherwise     = hledej ( tahni xs (hledej xss) )

-- Test: OK.
-- Vygeneruje tahy na pole, ktera nejsou v dosavadni ceste.
tahni :: Cesta -> [Cesta] -> [Cesta]
tahni [] ass     = ass
tahni (x:xs) ass = spoj (x:xs) (tah x) ass

-- Test: OK.
-- Propoji seznam moznych tahu s puvodni cestou.
spoj :: Cesta -> Cesta -> [Cesta] -> [Cesta]
spoj _ [] ass      = ass
spoj xs (y:ys) ass
       | unikat xs y == [] = spoj xs ys ass
       | otherwise         = (unikat xs y) : (spoj xs ys ass)

-- Test: OK.
-- Pokud pole neni v ceste, pak ho pridame.
unikat :: Cesta -> Pole -> Cesta
unikat xs y
       | clenem xs y == 1 = []
       | otherwise        = y:xs

-- Test: OK.
-- Vrati 1, pokud je jiz pole v ceste, jinak vrati 0.
clenem :: Cesta -> Pole -> Int
clenem [] _ = 0
clenem (x:xs) y
       | x==y = 1
       | otherwise = clenem xs y

-- Test: Lze tahnout i z pole mimo sachovnici.
-- Vytvori seznam poli, na kteje je mozne tahnout.
tah :: Pole -> [Pole]
tah (s,r) =  pridej (s+2,r+1)
            (pridej (s+2,r-1)
            (pridej (s+1,r+2)
            (pridej (s+1,r-2)
            (pridej (s-1,r+2)
            (pridej (s-1,r-2)
            (pridej (s-2,r+1)
            (pridej (s-2,r-1) [])))))))

-- Test: OK.
-- Pokud je (s,r) pole sachovnice, tak je prida do seznamu xs.
pridej :: Pole -> [Pole] -> [Pole]
pridej (s,r) xs
         = if ((s>0) && (s<6) && (r>0) && (r<6))
           then (s,r):xs
           else xs

-- Test: OK.
-- Zjisti pocet poli v ceste.
poli :: Cesta -> Int
poli [] = 0
poli (x:xs) = 1 + poli xs

-- 21. 12. 1998
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to