Difference between revisions of "99 questions/Solutions/18"

From HaskellWiki
Jump to navigation Jump to search
(I've come up with a solution that actually is an extended version of the 1st solution)
(16 intermediate revisions by 13 users not shown)
Line 4: Line 4:
   
 
<haskell>
 
<haskell>
slice xs (i+1) k = take (k-i) $ drop i xs
+
slice xs i k | i>0 = take (k-i+1) $ drop (i-1) xs
 
</haskell>
 
</haskell>
   
The same solution as above, but with guards:
+
The same solution as above, but the more paranoid (maybe too paranoid?) version of it (uses guards and Maybe):
   
 
<haskell>
 
<haskell>
slice [] _ _ = []
+
slice :: [a] -> Int -> Int -> Maybe [a]
slice xs k n | k == n = []
+
slice [] _ _ = Just []
| k > n = error "k > n"
+
slice xs k n | k == n = Just []
| k == 0 = take n xs
+
| k > n || k > length xs ||
  +
n > length xs || k < 0 || n < 0 = Nothing
| otherwise = drop (k-1) $ take n xs
 
  +
| k == 0 = Just (take n xs)
 
| otherwise = Just (drop (k-1) $ take n xs)
 
</haskell>
 
</haskell>
  +
  +
Or, a concise solution using list comprehension:
  +
  +
(Incorrect - only works on sequential data, needs update.)
  +
<haskell>
  +
--slice :: (Enum a) => [a] -> Int -> Int -> [a]
  +
--slice [] _ _ = []
  +
--slice xs m n = [(xs !! (m-1)) .. (xs !! (n-1))]
  +
</haskell>
  +
   
 
Or, an iterative solution:
 
Or, an iterative solution:
   
 
<haskell>
 
<haskell>
slice :: [a]->Int->Int->[a]
+
slice :: [a] -> Int -> Int -> [a]
slice lst 1 m = slice' lst m []
+
slice lst 1 m = slice' lst m []
 
where
 
where
 
slice' :: [a]->Int->[a]->[a]
 
slice' :: [a]->Int->[a]->[a]
 
slice' _ 0 acc = reverse acc
 
slice' _ 0 acc = reverse acc
 
slice' (x:xs) n acc = slice' xs (n - 1) (x:acc)
 
slice' (x:xs) n acc = slice' xs (n - 1) (x:acc)
  +
slice' [] _ _ = []
 
slice (x:xs) n m = slice xs (n - 1) (m - 1)
 
slice (x:xs) n m = slice xs (n - 1) (m - 1)
  +
slice [] _ _ = []
 
</haskell>
 
</haskell>
   
Line 33: Line 47:
 
<haskell>
 
<haskell>
 
slice :: [a] -> Int -> Int -> [a]
 
slice :: [a] -> Int -> Int -> [a]
  +
slice [] _ _ = []
 
slice (x:xs) i k
 
slice (x:xs) i k
| i > 1 = slice xs (i - 1) (k - 1)
+
| i > 1 = slice xs (i - 1) (k - 1)
| k < 1 = []
+
| k < 1 = []
| otherwise = x:slice xs (i - 1) (k - 1)
+
| otherwise = x:slice xs (i - 1) (k - 1)
 
</haskell>
 
</haskell>
   
Another way using <hask>splitAt</hask>, though not nearly as elegant as the <hask>take</hask> and <hask>drop</hask> version:
+
Another way using <hask>splitAt</hask>, though not nearly as elegant as the <hask>take</hask>&nbsp;and <hask>drop</hask>&nbsp;version:
   
 
<haskell>
 
<haskell>
Line 48: Line 63:
 
i' = i - 1
 
i' = i - 1
 
</haskell>
 
</haskell>
  +
A little cleaner, using the previous problem's split (a.k.a. <hask>splitAt</hask>):
  +
<haskell>
  +
slice xs (i+1) k = snd (split (fst (split xs k)) i)
  +
</haskell>
  +
  +
A solution using <hask>zip</hask>, <hask>filter</hask>&nbsp;then <hask>map</hask>&nbsp;seems straight-forward to me (''NB: this won't work for infinite lists''):
  +
  +
<haskell>
  +
slice xs i j = map snd
  +
$ filter (\(x,_) -> x >= i && x <= j)
  +
$ zip [1..] xs
  +
</haskell>
  +
A solution using list comprehension:
  +
<haskell>
  +
slice xs i k = [x | (x,j) <- zip xs [1..k], i <= j]
  +
</haskell>
  +
  +
Another simple solution using take and drop:
  +
<haskell>
  +
slice :: [a] -> Int -> Int -> [a]
  +
slice l i k
  +
| i > k = []
  +
| otherwise = (take (k-i+1) (drop (i-1) l))
  +
</haskell>
  +
  +
Zip, filter, unzip:
  +
<haskell>
  +
slice :: [a] -> Int -> Int -> [a]
  +
slice xs a b = fst $ unzip $ filter ((>=a) . snd) $ zip xs [1..b]
  +
</haskell>
  +
  +
Take and drop can be applied in the opposite order too:
  +
<haskell>
  +
slice xs i k = drop (i-1) $ take k xs
  +
</haskell>
  +
  +
Using a fold:
  +
<haskell>
  +
slice :: [a] -> Int -> Int -> [a]
  +
slice (x:xs) begin end = snd $ foldl helper (1, []) (x:xs)
  +
where helper (i, acc) x = if (i >= begin) && (i <= end) then (i+1, acc ++ [x]) else (i+1, acc)
  +
</haskell>
  +
  +
[[Category:Programming exercise spoilers]]

Revision as of 02:14, 4 July 2016

(**) Extract a slice from a list.

Given two indices, i and k, the slice is the list containing the elements between the i'th and k'th element of the original list (both limits included). Start counting the elements with 1.

slice xs i k | i>0 = take (k-i+1) $ drop (i-1) xs

The same solution as above, but the more paranoid (maybe too paranoid?) version of it (uses guards and Maybe):

slice :: [a] -> Int -> Int -> Maybe [a]
slice [] _ _ = Just []
slice xs k n 	| k == n = Just []
		| k > n || k > length xs || 
                  n > length xs || k < 0 || n < 0 = Nothing
		| k == 0 = Just (take n xs)
		| otherwise = Just (drop (k-1) $ take n xs)

Or, a concise solution using list comprehension:

(Incorrect - only works on sequential data, needs update.)

--slice :: (Enum a) => [a] -> Int -> Int -> [a]
--slice [] _ _ = []
--slice xs m n = [(xs !! (m-1)) .. (xs !! (n-1))]


Or, an iterative solution:

slice :: [a] -> Int -> Int -> [a]
slice lst    1 m = slice' lst m []
        where
                slice' :: [a]->Int->[a]->[a]
                slice' _ 0 acc = reverse acc
                slice' (x:xs) n acc = slice' xs (n - 1) (x:acc)
                slice' [] _ _ = []
slice (x:xs) n m = slice xs (n - 1) (m - 1)
slice []     _ _ = []

Or:

slice :: [a] -> Int -> Int -> [a]
slice [] _ _  = []
slice (x:xs) i k
 | i > 1      = slice xs (i - 1) (k - 1)
 | k < 1      = []
 | otherwise  = x:slice xs (i - 1) (k - 1)

Another way using splitAt, though not nearly as elegant as the take and drop version:

slice :: [a] -> Int -> Int -> [a]
slice xs i k = chunk
  where chop  = snd $ splitAt i' xs          -- Get the piece starting at i
        chunk = fst $ splitAt (k - i') chop  -- Remove the part after k
        i'    = i - 1

A little cleaner, using the previous problem's split (a.k.a. splitAt):

slice xs (i+1) k = snd (split (fst (split xs k)) i)

A solution using zip, filter then map seems straight-forward to me (NB: this won't work for infinite lists):

slice xs i j = map snd
               $ filter (\(x,_) -> x >= i && x <= j)
               $ zip [1..] xs

A solution using list comprehension:

slice xs i k = [x | (x,j) <- zip xs [1..k], i <= j]

Another simple solution using take and drop:

slice :: [a] -> Int -> Int -> [a]
slice l i k 
  | i > k = []
  | otherwise = (take (k-i+1) (drop (i-1) l))

Zip, filter, unzip:

slice :: [a] -> Int -> Int -> [a]
slice xs a b = fst $ unzip $ filter ((>=a) . snd) $ zip xs [1..b]

Take and drop can be applied in the opposite order too:

slice xs i k = drop (i-1) $ take k xs

Using a fold:

slice :: [a] -> Int -> Int -> [a]
slice (x:xs) begin end = snd $ foldl helper (1, []) (x:xs)
    where helper (i, acc) x = if (i >= begin) && (i <= end) then (i+1, acc ++ [x]) else (i+1, acc)