Skip to content

Instantly share code, notes, and snippets.

@MgaMPKAy
Created May 15, 2012 09:23
Show Gist options
  • Select an option

  • Save MgaMPKAy/2700339 to your computer and use it in GitHub Desktop.

Select an option

Save MgaMPKAy/2700339 to your computer and use it in GitHub Desktop.
module String50 where
import Data.List (inits, tails)
removeDuplicate [] = []
removeDuplicate [x, y] = if x == y then [x] else [x, y]
removeDuplicate (x:y:ys)
| x == y = removeDuplicate (y:ys)
| otherwise = x : removeDuplicate (y:ys)
squeeze [] = []
squeeze (x:xs)
| x `elem` ['\n', '\r', '_', '\t'] = squeeze xs
| otherwise = x : squeeze xs
mystrey n str
| n <= 0 = str
| n `rem` 2 == 1 = mystrey (n `div` 2) (str ++ str ++ "x")
| otherwise = mystrey (n `div` 2) str
isPalindrome s = reverse s == s
dnaComplement = map dnaComplement'
where
dnaComplement' 'A' = 'T'
dnaComplement' 'T' = 'A'
dnaComplement' 'C' = 'G'
dnaComplement' 'G' = 'C'
wastonCrickPalidrome s = s == dnaComplement (reverse s)
perfectShuffle s t
| lenS <= 1 = s ++ t
| otherwise = a ++ b
where
lenS = length s
a = perfectShuffle (subString 0 (lenS `div` 2) s)
(subString 0 (lenS `div` 2) t)
b = perfectShuffle (subString (lenS `div` 2) lenS s)
(subString (lenS `div` 2) lenS t)
subString begin end str = take (end - begin) (drop begin str)
perfectShuffle' [] y = y
perfectShuffle' x [] = x
perfectShuffle' [x] [y] = [x, y]
perfectShuffle' (x:xs) (y:ys) = x : y : perfectShuffle' xs ys
subSequence [] [] = True
subSequence _ [] = False
subSequence (x:xs) (y:ys)
| x == y = subSequence xs ys
| otherwise = subSequence (x:xs) ys
dnaToRna = map (\x -> if x == 'T' then 'U' else x)
reverse' str
| len <= 1 = str
| otherwise = reverse' t ++ reverse' h
where
h = subString 0 (len `div` 2) str
t = subString (len `div` 2) len str
len = length str
longestComplementedPalidrome dna = foldl step [] (subSeq dna)
where
step longDNA x
| isComplement x && length x > length longDNA = x
| otherwise = longDNA
isComplement x
| even len = x == dnaComplement (reverse x)
| otherwise = h == dnaComplement (reverse t)
&& t == dnaComplement (reverse h)
where
len = length x
h = subString 0 (len `div` 2) x
t = subString (len `div` 2 + 1) len x
subSeq ls = [t | i <- inits ls, t <- tails i, not $ null t]
powerSet [] = [[]]
powerSet [x] = [[x], []]
powerSet (x:xs) = map (x:) (powerSet xs) ++ powerSet xs
-- ex 15 10
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment