Skip to content

Commit

Permalink
converting haskell probs from scala/ruby
Browse files Browse the repository at this point in the history
  • Loading branch information
djtrack16 committed Aug 31, 2024
1 parent d6b5443 commit 005fcc9
Show file tree
Hide file tree
Showing 8 changed files with 259 additions and 97 deletions.
1 change: 1 addition & 0 deletions haskell/app/Main.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@

module Main where

main :: IO ()
Expand Down
80 changes: 80 additions & 0 deletions haskell/app/arithmetic.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,80 @@
{-# OPTIONS_GHC -Wno-overlapping-patterns #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}


module Arithmetic where

import qualified Data.List as L

-- P31 (**) Determine whether a given integer number is prime.
-- Prime numbers to test: http://compoasso.free.fr/primelistweb/page/prime/liste_online_en.php

isPrime :: Int -> Bool
isPrime n = not (any (\m -> mod n m == 0) [2.. sqrtT n])

sqrtT :: Int -> Int
sqrtT = floor . sqrt . fromIntegral

-- P32 (**) Determine the greatest common divisor of two positive integer numbers.
gcdNew :: Int -> Int -> Int
gcdNew a b = if b == 0 then a else gcdNew b (mod a b)

-- P33 (*) Determine whether two positive integer numbers are coprime.
isCoprime :: Int -> Int -> Bool
isCoprime a b = gcdNew a b == 1

-- P34 (**) Calculate Euler’s totient function ϕ(m). Euler’s so-called totient function
-- ϕ(m) is defined as the number of positive integers r(1<=r<=m) that are coprime to m.
totient :: Int -> Int
totient m = length (filter (`isCoprime` m) [1..m])

-- P35 (**) Determine the prime factors of a given positive integer.
-- Construct a flat list containing the prime factors in ascending order.
primeFactors :: Int -> [Int]
primeFactors n = let divs = filter (\k -> mod n k == 0) [2..n]
factor = if null divs then 0 else head divs
in if factor == 0 then [] else factor : primeFactors (div n factor)

-- P36 (**) Determine the prime factors of a given positive integer
-- Construct a list containing the prime factors and their multiplicity.
primeFactorsMultiplicity :: Int -> [(Int, Int)]
primeFactorsMultiplicity n = map (\facs -> (head facs, length facs)) (L.group (primeFactors n))

-- P37 (**) Calculate Euler’s totient function ϕ(m) (improved).
-- See problem P34 for the definition of Euler’s totient function.  If the list of the prime factors of a number
-- m is known in the form of problem P36 then the function ϕ(m) can be efficiently calculated as follows
-- https://aperiodic.net/pip/scala/s-99/#p37
-- '^' only works for positive exponents, should be OK here
totientImproved :: Int -> Int
totientImproved n = product (
map (
\(factor, multiplicity) -> (factor - 1)*(factor^(multiplicity - 1))
)
(primeFactorsMultiplicity n)
)

-- P39 (*) A list of prime numbers.
-- Given a range of integers by its lower and upper limit, construct a list of all prime numbers in that range.
listPrimesInRange :: Int -> Int -> [Int]
listPrimesInRange low high = filter isPrime [low..high]

-- P40 (**) Goldbach’s conjecture.
-- Goldbach’s conjecture says that every positive even number greater than 2 is the sum of two prime numbers.
-- E.g. 28=5+23.  It is one of the most famous facts in number theory that has not been proved to be correct in the general case.
-- It has been numerically confirmed up to very large numbers (much larger than Scala’s Int can represent).
-- Write a function to find the two prime numbers that sum up to a given even integer.
goldbachNumbers :: Int -> [Int]
goldbachNumbers n = let pairs = filter (\m -> isPrime m && isPrime (n - m)) [2..n]
m = if null pairs then 0 else m
in if m > 0 then [] else [m, n - m]

-- P41 (**) A list of Goldbach compositions.
-- Given a range of integers by its lower and upper limit, print a list of all even numbers and their Goldbach composition.
goldbachCompositions :: Int -> Int -> [(Int, [Int])]
goldbachCompositions low high = let lo = if even low then low else succ low
hi = if even high then high else pred high
in map (\n -> (n, goldbachNumbers n)) [lo,lo+2..hi]
{-
-}
97 changes: 0 additions & 97 deletions haskell/app/list.hs

This file was deleted.

178 changes: 178 additions & 0 deletions haskell/app/lists.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,178 @@
{-# OPTIONS_GHC -Wno-overlapping-patterns #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}


module Lists where

import qualified Data.List as L

data NestedList a =
Object a | Array[NestedList a]

-- P01. Find the last element in a list
lastBuiltIn :: [a] -> a
lastBuiltIn = last

lastElement :: [a] -> a
lastElement [x] = x
lastElement (_:xs) = lastElement xs
lastElement [] = error "The list is already empty"

-- PO2. Find the penultimate element in a list

penultimate :: [a] -> a
penultimate (x:xs) = if length xs == 1 then last xs else penultimate xs --(tail . init) xs
penultimate [] = error "The list is already empty"
penultimate [x] = error "List only has 1 element"

-- P03. Find the K'th element of a list. The first element in the list is number 1.

kthElement :: ([a], Int) -> a
kthElement (_, 0) = error "k must be greater than 1"
kthElement ([x], 1) = x
kthElement (xs, k) = if k > length xs then error "k must be less than lenghth of list" else last (take k xs)

-- P04. Find the number of elements of a list (besides built in fns)

listLength :: [a] -> Int
listLength [] = 0
listLength xs = 1 + listLength (tail xs)

-- P05. Reverse a list.

reverseList :: [a] -> [a]
reverseList [] = []
reverseList xs = last xs : reverseList (init xs)

-- P06. Find out whether a list is a palindrome.

isPalindrome :: Eq a => [a] -> Bool
isPalindrome [] = True
isPalindrome xs = head xs == last xs && isPalindrome (init (tail xs))

-- P07. Flatten a nested list structure.

flattenList :: NestedList[a] -> [a]
flattenList (Object x) = x
flattenList (Array []) = []
flattenList (Array (x:xs)) = flattenList x ++ flattenList (Array xs)

-- P08 (**) Eliminate consecutive duplicates of list elements.
-- If a list contains repeated elements they should be replaced with a single copy of the element.
-- The order of the elements should not be changed.

removeConsecutiveDuplicates :: Eq a => [a] -> [a]
removeConsecutiveDuplicates (x:y:ys) = ([x] ++ [y | x /= y]) ++ removeConsecutiveDuplicates ys
removeConsecutiveDuplicates [] = [] -- both [] and [x] return here
removeConsecutiveDuplicates [x] = [x]

-- P09 Pack consecutive duplicates of list elements into sublists.
-- If a list contains repeated elements they should be placed in separate sublists.
-- AKA do this :P https://hackage.haskell.org/package/grouped-list-0.2.3.0/docs/src/Data.GroupedList.html#groupedGroups
pack :: Eq a => [a] -> [[a]]
pack [] = []
pack [x] = [[x]]
pack (x:xs) = (x: takeWhile (==x) xs) : pack (dropWhile (==x) xs)

-- P10 Run-length encoding of a list.
-- Use the result of problem P09 to implement the so-called run-length encoding data compression method.
-- Consecutive duplicates of elements are encoded as tuples (N, E) where N is the number of duplicates of the element

encode :: Eq a => [a] -> [(Int, a)]
encode xs = map (\item -> (length item, head item)) (pack xs)

{-
-- P11 Modified run-length encoding. Modify the result of problem P10 in such a way that
-- if an element has no duplicates it is simply copied into the result list.  Only elements
-- with duplicates are transferred as (N, E) terms.
encodeModified :: Eq a => [a] -> Either [a] [(Int, a)]
encodeModified xs = map (\pair -> if l == 1 then elem else (l, elem)) (pack xs)
-}

-- P12 Decode a run-length encoded list.
-- Given a run-length code list generated as specified in problem P10, construct its uncompressed version.
decode :: [(Int, a)] -> [a]
decode [] = []
decode ((length, item):rest) = replicate length item ++ decode rest

-- P13 (**) Run-length encoding of a list (direct solution).
-- Implement the so-called run-length encoding data compression method directly.
-- I.e. don’t use other methods you’ve written (like P09’s pack); do all the work directly.
encodeDirect :: Eq a => [a] -> [(Int, a)]
encodeDirect [] = []
encodeDirect (x:xs) = let(first, rest) = span (==x) xs
in (
1 + length first,
x
) : encodeDirect rest


-- P15 (**) Duplicate the elements of a list a given number of times.

duplicateN :: (Int, [a]) -> [a]
duplicateN (n, xs) = concatMap (replicate n) xs

-- P16 (**) Drop every Nth element from a list.

dropN :: Int -> [a] -> [a]
dropN _ [] = []
dropN n xs = take (n-1) xs ++ dropN n (drop n xs)

-- P18 (**) Extract a slice from a list. Given two indices, I and K,
-- the slice is the list containing the elements from and including the
-- Ith element up to but not including the Kth element of the original list.
-- Start counting the elements with 0.

slice :: Int -> Int -> [a] -> [a]
slice i k xs = take (k-i) (drop i xs)

-- P19 (**) Rotate a list N places to the left.

rotate :: Int -> [a] -> [a]
rotate 0 xs = xs
rotate n xs = let remainder = mod n (length xs)
pivot = if remainder < 0 then remainder + length xs else remainder
in drop pivot xs ++ take pivot xs
{-
var pivot = n % xs.length
pivot = if (pivot < 0) pivot + xs.length else pivot
xs.drop(pivot) ++ xs.take(pivot)
let index = if n > 0 then n else length xs - abs n
(b,c) = splitAt index xs
in concat (reverse (head c ++ head b))
-}

-- P26 (**) Generate the combinations of K distinct objects chosen from the N elements of a list.
-- In how many ways can a committee of 3 be chosen from a group of 12 people?  We all know that there are
-- C(12,3)= 220 possibilities
-- C(N,K) denotes the well-known binomial coefficient). For pure mathematicians, this result may be great.
-- But we want to really generate all the possibilities.
combinations :: Int -> [a] -> [[a]]
combinations 0 _ = []
combinations k [] = [[]]
combinations k (first:rest) = map (first:) (combinations (k-1) rest) ++ combinations k rest

-- P28 (**) Sorting a list of lists according to length of sublists.
-- a) We suppose that a list contains elements that are lists themselves.
-- The objective is to sort the elements of the list according to their length.
-- E.g. short lists first, longer lists later, or vice versa.

lsort :: [[a]] -> [[a]]
lsort = L.sortBy (\a b -> compare (length a) (length b))

-- P28b) Again, we suppose that a list contains elements that are lists themselves.
-- But this time the objective is to sort the elements according to their length frequency;
-- i.e. in the default, sorting is done ascendingly, lists with rare lengths are placed first,
-- others with a more frequent length come later.

lsortFreq :: [[a]] -> [[a]]
lsortFreq xs = let cmp a b = compare (length a) (length b)
in concat (L.sortBy cmp (groupedListsByLength xs))

groupedListsByLength :: [[a]] -> [[[a]]]
groupedListsByLength xs = L.groupBy (\b c -> length b == length c) (lsort xs)

Binary file not shown.
Binary file not shown.
Binary file not shown.
Binary file not shown.

0 comments on commit 005fcc9

Please sign in to comment.