Skip to content

Commit

Permalink
Changed defs and intSeq files into modules
Browse files Browse the repository at this point in the history
  • Loading branch information
barbuz committed May 14, 2021
1 parent 40fbd35 commit 03b3cf9
Show file tree
Hide file tree
Showing 4 changed files with 40 additions and 31 deletions.
30 changes: 28 additions & 2 deletions defs.hs → Defs.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,17 @@
{-# LANGUAGE UndecidableInstances, FlexibleInstances, FlexibleContexts, BangPatterns #-}

module Defs where
-- Built-in functions

import Data.Function (fix)
import qualified Data.Char as C
import Data.Char (chr,ord)
import Data.List
import qualified Data.Set as S (member, insert, singleton)
import Data.Ord (comparing)
import Data.Bits ((.&.), (.|.))
import Data.Ratio ((%), numerator, denominator)

import Numeric (showFFloat)

-- Type of numeric values: integer fractions and Doubles
Expand Down Expand Up @@ -366,6 +378,20 @@ instance (Concrete a, Concrete b) => Concrete (a, b) where
roundAway :: Double -> Integer
roundAway d = if d<0 then floor d else ceiling d

--Primes (quite efficient implementation, but not the most efficient)
primes_list = 2 : oddprimes
where
oddprimes = sieve [3,5..] 9 oddprimes
sieve (x:xs) q ps@ ~(p:t)
| x < q = x : sieve xs q ps
| otherwise = sieve (xs `minus` [q, q+2*p..]) (head t^2) t
minus (x:xs) (y:ys) = case (compare x y) of
LT -> x : minus xs (y:ys)
EQ -> minus xs ys
GT -> minus (x:xs) ys
minus xs _ = xs


-- Built-in functions

func_fix :: (a -> a) -> a
Expand Down Expand Up @@ -1041,7 +1067,7 @@ func_isprime :: TNum -> TNum
func_isprime p | n :% 1 <- p,
n >= 2,
probablePrime n
= func_oelem (func_intseq 'p') p
= func_oelem primes_list p
| otherwise = 0
where
probablePrime :: Integer -> Bool
Expand Down Expand Up @@ -1603,4 +1629,4 @@ func_idx2d :: Husky a => (TNum, TNum) -> [[a]] -> a
func_idx2d (x, y) = func_index y . func_index x

func_idx2d2 :: Husky a => [[a]] -> (TNum, TNum) -> a
func_idx2d2 = flip func_idx2d
func_idx2d2 = flip func_idx2d
8 changes: 4 additions & 4 deletions Husk.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,14 +71,14 @@ consoleOpts = [Option ['b'] ["bytes"] (NoArg $ Format Bytes) "take input as byte
parseFormat "v" = Verbose
parseFormat _ = error "Bad format specifier"

-- Template files as String constants
templateFile :: String
templateFile = [litFile|header.hs|] ++ "\n" ++ [litFile|defs.hs|] ++ "\n" ++ [litFile|intSeq.hs|] ++ "\n"
-- Imports needed for transpiled file
fileImports :: String
fileImports = unlines $ map ("import "++) $ ["Defs", "IntSeq", "System.Environment (getArgs)"]

-- Produce Haskell file from list of type-inferred lines
produceFile :: [(Int, CType, Exp (Lit CType))] -> String
produceFile exprs =
templateFile ++
fileImports ++
progLines ++
"main :: IO ()\n" ++
"main = do{[" ++ intercalate "," argList ++ "] <- getArgs; " ++
Expand Down
20 changes: 8 additions & 12 deletions intSeq.hs → IntSeq.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,11 @@
{-# LANGUAGE UndecidableInstances, FlexibleInstances, FlexibleContexts, BangPatterns #-}

module IntSeq where
-- Built-in integer sequences

import Data.List
import Defs

func_intseq :: Char -> [TNum]

--Alternate signs
Expand Down Expand Up @@ -37,18 +43,8 @@ func_intseq 'f' = fibs
where
fibs = 1 : 1 : zipWith (+) fibs (tail fibs)

--Primes (quite efficient implementation, but not the most efficient)
func_intseq 'p' = 2 : oddprimes
where
oddprimes = sieve [3,5..] 9 oddprimes
sieve (x:xs) q ps@ ~(p:t)
| x < q = x : sieve xs q ps
| otherwise = sieve (xs `minus` [q, q+2*p..]) (head t^2) t
minus (x:xs) (y:ys) = case (compare x y) of
LT -> x : minus xs (y:ys)
EQ -> minus xs ys
GT -> minus (x:xs) ys
minus xs _ = xs
--Primes (defined in Defs.hs)
func_intseq 'p' = primes_list

--Ruler sequence (exponent of highest power of 2 dividing n), OEIS A007814
func_intseq 'r' = 0:concatMap(\x->[x+1,0])(func_intseq 'r')
Expand Down
13 changes: 0 additions & 13 deletions header.hs

This file was deleted.

0 comments on commit 03b3cf9

Please sign in to comment.