Haskell help!

Marc Ziegert coeus@gmx.de
Thu, 27 Mar 2003 00:50:57 +0100


--------------Boundary-00=_XKRD6KRO09B4VGBLEXFE
Content-Type: text/plain;
  charset="windows-1252"
Content-Transfer-Encoding: quoted-printable

done.
- marc


Am Mittwoch, 26. M=E4rz 2003 23:32 schrieb Weix, Rachel Lynn:
> P.S.  The example given is for the set of sequences/strings (The,Master=
s)
>
> =09-----Original Message-----
> =09From: Weix, Rachel Lynn
> =09Sent: Wed 3/26/2003 4:30 PM
> =09To: coeus@gmx.de
> =09Cc: haskell@haskell.org
> =09Subject: RE: Haskell help!
>
>
> =09Currently I'm having problems with type checking due to Haskell bein=
g a
> strongly typed language.  In order to return all optimal solutions, my
> professor suggested I create a list of tuples if they all have the same
> score, as indicated in my new maxSeq method (see attachment).  However,
> this means that the maxSeq method would return type [[(Char,Char)]].  S=
ince
> maxSeq and getSeq must return the same type, I end up changing all my
> signatures and end up with lots of problems.  In my caseX methods, I ca=
n't
> append [(Char)] to [[(Char,Char)]], and it also messes up trying to get=
 my
> score of each tuple, etc.  I've been trying to solve the problem in Sch=
eme
> first but even then I'm having problems, and Scheme is only loosely typ=
ed.=20
> Any suggestions?  The format should be something like the following
> (partial example):
>
> =09[ [(-,M)] [(T,a)(h,s)(-,t)(e,e)(-,r)(-,s)] [(-,s)(h,t)(e,e)(-,r)(-,s=
)]]].
>
> =09Once I get back my list, I need to pair everything up in order to re=
turn a
> list of optimal solutions.  Taking the previous example, it would be th=
e
> following when paired up correctly:
>
> =09[ [(-,M)(T,a)(h,s)(-,t)(e,e)(-,r)(-,s)],
> [(-,M)(T,a)(-,s)(h,t)(e,e)(-,r)(-,s)] ]
>
> =09From there, I find which sequence has the maximum score.  I then wal=
k
> through the list again, making a list of all the sequences that have th=
at
> score.  These two steps seem fairly trivial, it's all the above stuff w=
hich
> I'm struggling on.
>
> =09Rachel
>
> =09-----Original Message-----
> =09From: Marc Ziegert [mailto:coeus@gmx.de]
> =09Sent: Tue 3/25/2003 3:13 PM
> =09To: Weix, Rachel Lynn
> =09Cc:
> =09Subject: Re: Haskell help!
>
>
>
> =09=09maxSeq had one mistake: || instead of &&
>
> =09=09i will think about the problem itself, before rewriting all.
>
> =09=09this is the file a little bit more in haskell style.
>
> =09=09Am Dienstag, 25. M=E4rz 2003 20:16 schrieben Sie:
> =09=09> I found my two mistakes, plus I fixed the method my Professor s=
aid was
> =09=09> incorrect.  Now I just have to be able to find ALL optimal solu=
tions,
> =09=09> instead of just one.  Hooray!
> =09=09>
> =09=09> Rachel

--------------Boundary-00=_XKRD6KRO09B4VGBLEXFE
Content-Type: text/plain;
  charset="windows-1252";
  name="prog1.hs"
Content-Transfer-Encoding: 7bit
Content-Disposition: attachment; filename="prog1.hs"

module Main where

type VSeqs = (Integer,[(String,String)]) -- valued sequences


type VS_matrix = [[VSeqs]]


emptyVS :: VSeqs
emptyVS = (0,[("","")])

rightmostCol :: String -> [VSeqs]
rightmostCol "" = [emptyVS]
rightmostCol (c:cs) = (v-1,[('~':s1,c:s2)]) : above
                      where above@((v,(s1,s2):_):_) = rightmostCol cs


nextCol :: Char -> String -> [VSeqs] -> [VSeqs]
nextCol c "" ((v,(s1,s2):_):_) = (v-1,(c:s1,'~':s2):[]):[]
nextCol c str2 (vs:vsr) = makeEntry c str2 (head above) vs (head vsr) : above
                          where above = nextCol c (tail str2) vsr


makeEntry :: Char-> String -> VSeqs -> VSeqs -> VSeqs -> VSeqs
makeEntry c str2@(h:_) above@(va,sa) right@(vr,sr) aboveright@(vd,sd) = maxEntry fa fr fd
                                                                        where fa = (va-1, append '~' h  sa )
                                                                              fr = (vr-1, append  c '~' sr )
                                                                              fd = (vd+v, append  c  h  sd )
                                                                              v = if c==h then 1 else -1
                                                                              append l r tups = [ (l:ls,r:rs) | (ls,rs)<-tups ]

maxEntry :: VSeqs -> VSeqs -> VSeqs -> VSeqs
maxEntry a@(va,_) b@(vb,_) c@(vc,_) = if va>vb then if va>vc then a
                                                             else c
                                               else if vb>vc then b
                                                             else c
                          
                          
fillmatrix :: String -> String -> VS_matrix
fillmatrix str1 str2 = scanr xcc (rightmostCol str2) str1
                       where xcc :: Char -> [VSeqs] -> [VSeqs]
                             xcc x s = nextCol x str2 s


findBestSeqs :: String -> String -> VSeqs
findBestSeqs str1 str2 = head $ head $ fillmatrix str1 str2




main :: IO ()
main = do putStr                         "\"icecream\" \"scheme\"  : "
          putStrLn $ show $ findBestSeqs   "icecream"   "scheme"
          putStr                         "\"hate\"     \"hatter\"  : "
          putStrLn $ show $ findBestSeqs   "hate"       "hatter"
          putStr                         "\"scheme\"   \"saturn\"  : "
          putStrLn $ show $ findBestSeqs   "scheme"     "saturn"
          putStr                         "\"saturn\"   \"scheme\"  : "
          putStrLn $ show $ findBestSeqs   "saturn"     "scheme"
          putStr                         "\"saturn\"   \"hatter\"  : "
          putStrLn $ show $ findBestSeqs   "saturn"     "hatter"
          putStr                         "\"hatter\"   \"saturn\"  : "
          putStrLn $ show $ findBestSeqs   "hatter"     "saturn"
          putStr                         "\"mad\"      \"saturn\"  : "
          putStrLn $ show $ findBestSeqs   "mad"        "saturn"
          putStr                         "\"snowball\" \"icecream\": "
          putStrLn $ show $ findBestSeqs   "snowball"   "icecream"
          putStr                         "\"mad\"      \"computer\": "
          putStrLn $ show $ findBestSeqs   "mad"        "computer"
          putStr                         "\"mad\"      \"snowball\": "
          putStrLn $ show $ findBestSeqs   "mad"        "snowball"

          
{-




--Sample Sequences
icecream = "icecream"
scheme = "scheme"
saturn = "saturn"  -- "saaturn"
mad = ['m','a','d']
hatter = ['h','a','t','t','e','r']
hate = ['h','a','t','e']
snowball = ['s','n','o','w','b','a','l','l']
computer = ['c','o','m','p','u','t','e','r']
coffee = ['c','o','f','f','e','e']


--Function that's called in a console window which does the sequence 
--alignment and puts the two optimal sequences back together
printSeq :: String -> String -> (String,String)
printSeq s1 s2 = unzip (getSeq s1 s2)


--Main function of the program which does the actual sequence alignment
getSeq :: String -> String -> [(Char,Char)]
getSeq [] [] = []
getSeq [] s2 = case2 [] s2
getSeq s1 [] = case3 s1 []
getSeq s1 s2 = let a1 = case1 s1 s2;
                   a2 = case2 s1 s2;
                   a3 = case3 s1 s2;
               in maxSeq a1 a2 a3


case1 :: [Char] -> [Char] -> [(Char,Char)]
case1 s1 s2 = [(head s1,head s2)] ++ getSeq (tail s1) (tail s2)

case2 :: [Char] -> [Char] -> [(Char,Char)]
case2 s1 s2 = [('-',head s2)] ++ getSeq s1 (tail s2)

case3 :: [Char] -> [Char] -> [(Char,Char)]
case3 s1 s2 = [(head s1,'-')] ++ getSeq (tail s1) s2


--Grab the score of one tuple (a possible alignment)
score :: (Eq a) => (a,a) -> Integer
score (c1,c2) | c1==c2    = 1
              | otherwise = -1
            
--Sum up the score for a sequence
scoreSum :: (Eq a) => [(a,a)] -> Integer
scoreSum seq = sum $ map score seq


--Returns a solution
maxSeq :: (Eq a) => [(a,a)] -> [(a,a)] -> [(a,a)] -> [(a,a)]
maxSeq a1 a2 a3
        | s1 > s2 && s1 > s3 = a1
        | s3 > s1 && s3 > s2 = a3
        | otherwise          = a2
        where s1 = scoreSum a1
              s2 = scoreSum a2
              s3 = scoreSum a3

-}
--------------Boundary-00=_XKRD6KRO09B4VGBLEXFE--