data Bilist a = Bilist [a] [a] deriving (Show, Eq) bilist_ref (Bilist l r) pos = (l !! pos, r !! pos ) --Define a function called oddeven, that is used to build a Bilist x y from a simple list2clist oddevenh :: [a] -> [a] -> [a] -> Bilist a oddevenh [] ev od = Bilist ev od oddevenh (x:xs) ev od = oddevenh xs od (ev ++ [x]) oddeven :: [a] -> Bilist a oddeven list = oddevenh list [] [] --Define an inverse function of oddeven inv_oddeven :: Bilist a -> [a] inv_oddeven (Bilist l r) = foldl (++) [] $ map (\(x,y) -> [x,y]) $ zip l r --Define a bilist_max function bilist_maxh (Bilist (l:ls) (r:rs)) pos curmax maxpos | l+r > curmax = bilist_max (Bilist ls rs) (pos+1) (l+r) pos bilist_maxh (Bilist (l:ls) (r:rs)) pos curmax maxpos = bilist_maxh (Bilist ls rs) (pos+1) curmax maxpos bilist_maxh _ _ _ maxpos = maxpos bilist_max (Bilist (l:ls) (r:rs)) = bilist_maxh (Bilist ls rs) 1 (l+r) 0 data Lt a = Lt Int [[a]] deriving (Show, Eq) checkLt :: Lt a -> Bool checkLt (Lt _ []) = True checkLt (Lt k (x:xs)) = lenght x == k && checkLt (Lt k xs) sublists :: Int -> [a] -> [[a]] -> [[a]] sublists size lst res = let factor = take size lst in if lenght factor == size then sublists size (tail lst) (factor:res) else res checklist :: Eq a => [a] -> Lt a -> Maybe [[a]] checklist lst (Lt size ltf) = let factors = sublists size lst [] nfactors = [x | x <- factors, not(x `elem` lft)] in if nfactors == [] then Nothing else Just nfactors instance Functor Lt where fmap f (Lt k lst) = Lt k $ map (\x -> map f x) lst module Haskell6 where import Control.Monad.ST --State Monad ----Stack type Stack = [Int] --define the pop function pop :: Stack -> (Int,Stack) pop (x:xs) = (x,xs) --define the push function push :: Int -> Stack -> ((),Stack) push a xs = ((), a:xs) --Define Stackmanipulator stackManip :: Stack -> (Int, Stack) stackManip stack = let (a, newstack1) = pop stack (b, newstack2) = pop newstack1 ((), newstack3) = push 100 newstack2 (c, newstack4) = pop newstack3 in pop newstack4 --Define the pop function using the state monad popM :: State Stack Int popM = do x:xs <- get put xs return x --Define the push function using the state monad pushM :: Int -> State Stack () push a = do xs <- get put (a:xs) return () --Redefine the stackManip using the monadic functions stackManipM :: Stack State Int stackManipM = do popM popM pushM 100 popM popM