Safe Haskell | None |
---|
Synopsis
- print_ascii_c :: IO ()
- print_ascii_f :: IO ()
- class Cnum a where
- class Dnum a b where
- class Add a b where
- data CodeBlock = CodeBlock {
- codeBlockId :: Int64
- header :: Text
- codeblock :: Text
- addedtime :: Int64
- score :: Int64
- data SqliteMaster = SqliteMaster {
- x_type :: Text
- x_name :: Text
- x_tbl_name :: Text
- x_rootpage :: Integer
- x_sql :: Text
- data UpdateCodeBlock = UpdateCodeBlock {}
- data UpdateCodeBlockX = UpdateCodeBlockX {}
- data CodeBlockReply = CodeBlockReply {}
- data ReplyCode = ReplyCode {}
- data CommandService = CommandService {}
- type CSSPro = (String, String)
- epsilon__ :: Double
- div' :: Int -> Int -> Double
- divInteger :: Integer -> Integer -> Double
- divII :: (Num a, Fractional a) => Integer -> Integer -> a
- rf :: (Real a, Fractional b) => a -> b
- fi :: (Integral a, Num b) => a -> b
- mat :: [[Integer]]
- matr :: [[Ratio Integer]]
- mat' :: [[[Char]]]
- eps :: (Num a, Ord a) => a -> a -> a -> Bool
- data C = C {}
- data RedisGroup
- redisBound :: RedisGroup -> Integer
- con :: C -> C
- mag :: C -> Float
- norm :: C -> Float
- re :: C -> Float
- im :: C -> Float
- co :: C -> (Float, Float)
- toPolar :: C -> (Float, Float)
- toCard :: (Float, Float) -> C
- loge :: Double -> Double
- sqrtC :: C -> C
- sqrtC' :: C -> C
- radianToDegree :: Float -> Float
- degreeToRadian :: Float -> Float
- tri :: C -> (Float, Float, Float)
- data GPoint = GPoint Int Int
- getX :: GPoint -> Int
- getY :: GPoint -> Int
- toUpperStr :: String -> String
- lowerStr :: String -> String
- upperStr :: String -> String
- upperChar :: Char -> Char
- toLowerStr :: String -> String
- concatStr :: [String] -> String -> String
- cat :: String -> IO ()
- readDirMatchKey :: FilePath -> String -> String -> IO [(String, String)]
- containStr :: String -> String -> Bool
- containAscii :: String -> Bool
- containNonAsciiList :: [String] -> [(Integer, String)]
- matchAny :: String -> String -> Maybe (Int, Int)
- matchAnyRegex :: Regex -> String -> Maybe (Int, Int)
- type SKey = String
- matchScore :: SKey -> String -> (Int, String)
- matchScoreList :: SKey -> [String] -> [(Int, String)]
- fileContainNonAscii :: FilePath -> IO [(Integer, String)]
- fileContain :: FilePath -> String -> IO [String]
- fileHas :: (String -> Bool) -> FilePath -> IO [String]
- filterList :: (Bool -> Bool) -> [String] -> [String] -> [String]
- intersectSet :: (Eq a, Hashable a) => [a] -> [a] -> [a]
- diffList :: (Eq a, Hashable a) => [a] -> [a] -> ([a], [a])
- interList :: (Eq a, Hashable a) => [a] -> [a] -> [a]
- intersectFile :: FilePath -> FilePath -> IO [String]
- filterNonEmpty :: [String] -> [String]
- containPrefix :: String -> String -> Bool
- containSuffix :: String -> String -> Bool
- hasPrefix :: String -> String -> Bool
- hasSuffix :: String -> String -> Bool
- hasStr :: String -> String -> Bool
- isImage :: String -> Bool
- lsTable :: String -> IO [[String]]
- replaceFileLineEscape :: String -> String -> FilePath -> IO [String]
- replaceFileLineEscapeStrict :: FilePath -> String -> String -> IO [String]
- strWithSlash :: String -> String
- replaceFileLine :: String -> String -> FilePath -> IO [String]
- redisExtractCppAronLib :: String -> [String] -> [([String], Integer, [String])]
- readTagsFile :: FilePath -> IO [(String, String)]
- extraTags :: [String] -> [(String, String)]
- replaceList :: [String] -> String -> String -> [String]
- searchSplitAny :: String -> String -> [(String, String, String)]
- searchSplitWord :: String -> String -> [(String, String, String)]
- searchReplaceAny :: String -> String -> String -> String
- searchReplaceAnyTup :: String -> (String, String) -> String
- searchReplaceAnySBS :: ByteString -> ByteString -> ByteString -> ByteString
- searchReplace :: String -> String -> String -> String
- searchReplaceWord :: String -> (String, String) -> String
- interleave :: [a] -> [a] -> [a]
- intersperseInner :: a -> [a] -> [a]
- listIn :: a -> [a] -> [a]
- listOut :: a -> [a] -> [a]
- intersperseOuter :: a -> [a] -> [a]
- repeat' :: Integer -> a -> [a]
- repeatN :: Integer -> a -> [a]
- replicateN :: Integer -> a -> [a]
- replicate' :: Int -> a -> [a]
- fillList :: Integer -> [Integer] -> [Integer]
- readFileStrict :: FilePath -> IO String
- readFileListStrict :: FilePath -> IO [String]
- readFileBSList :: FilePath -> IO [ByteString]
- readFileBS :: FilePath -> IO ByteString
- readFileSText :: FilePath -> IO Text
- readFileSTextList :: FilePath -> IO [Text]
- charToStrictByteString :: Char -> ByteString
- plines :: String -> [String]
- breakNewline :: String -> (String, String)
- replaceByteStringFile :: FilePath -> ByteString -> ByteString -> IO ByteString
- replaceFileWithBSToNew :: FilePath -> (ByteString, ByteString) -> FilePath -> IO ()
- replaceFileWithStrToNew :: FilePath -> (String, String) -> FilePath -> IO ()
- replaceFileWithStr :: String -> String -> FilePath -> IO ()
- replaceFileWithWord :: String -> String -> FilePath -> IO ()
- replaceFileListWord :: [(String, String)] -> FilePath -> IO ()
- replaceFileListStr :: [(String, String)] -> FilePath -> IO ()
- searchReplaceListWord :: [(String, String)] -> String -> String
- searchReplaceListStr :: [(String, String)] -> String -> String
- replaceDirWithStr :: String -> String -> FilePath -> IO ()
- replaceRegex :: Regex -> String -> String -> String
- readFileRepPat :: FilePath -> ByteString -> ByteString -> IO ByteString
- replaceFileWithPat :: FilePath -> ByteString -> ByteString -> IO ByteString
- toStrictBS :: ByteString -> ByteString
- strictBSToString :: ByteString -> String
- emptySBS :: ByteString
- toSBS :: Typeable a => a -> ByteString
- toLBS :: Typeable a => a -> ByteString
- toSText :: Typeable a => a -> Text
- toLText :: Typeable a => a -> Text
- toStr :: Typeable a => a -> String
- catMaybe :: Maybe [a] -> Maybe [a] -> Maybe [a]
- removeSpace :: String -> String
- isEmpty :: String -> Bool
- escapeHtml :: String -> String
- escapeAmpersand :: String -> String
- escapePartial :: String -> String
- escapeXML :: String -> String
- removeIndex :: Int -> [a] -> [a]
- removeIndex_new :: Integer -> [a] -> [a]
- removeRowCol :: Integer -> Integer -> [[a]] -> [[a]]
- principleSubmatrix :: Int -> [[a]] -> [[a]]
- dropEnd :: Integer -> [a] -> [a]
- takeEnd :: Integer -> [a] -> [a]
- takeX :: Integer -> [a] -> [a]
- dropX :: Integer -> [a] -> [a]
- takeWhileX :: (a -> Bool) -> [a] -> [a]
- takeBS :: Integer -> ByteString -> ByteString
- dropBS :: Integer -> ByteString -> ByteString
- splitBS :: Word8 -> ByteString -> [ByteString]
- trimWS :: String -> String
- trimAll :: String -> String
- trimT :: Text -> Text
- trimBoth :: String -> String
- trimLBS :: ByteString -> ByteString
- trimStart :: String -> String
- trimEnd :: String -> String
- splitListEmptyLine :: [String] -> [[String]]
- splitListHalf :: [String] -> ([String], [String])
- t1 :: (a, b, c) -> a
- t2 :: (a, b, c) -> b
- t3 :: (a, b, c) -> c
- tuplify2 :: [a] -> (a, a)
- tuplify3 :: [a] -> (a, a, a)
- splitListWhen :: (a -> Bool) -> [a] -> [[a]]
- lengthcurve :: (Double -> Double) -> (Int, Int) -> Double
- lengthcurveInter :: (Double -> Double) -> (Int, Int) -> Int -> Double
- isBalanced3 :: String -> String -> Bool
- isBalanced2 :: String -> String -> (String, Bool)
- findBalance :: [(Integer, String)] -> String -> ([(Integer, String)], Bool)
- isBalanced :: String -> Bool
- strToLazyText :: String -> Text
- lazyTextToStr :: Text -> String
- strToStrictText :: String -> Text
- strictTextToStr :: Text -> String
- lazyTextToLazyByteString :: Text -> ByteString
- lazyByteStringToLazyText :: ByteString -> Text
- strictTextToStrictByteString :: Text -> ByteString
- strictByteStringToStrictText :: ByteString -> Text
- strictByteStringToLazyByteString :: ByteString -> ByteString
- lazyByteStringToStrictByteString :: ByteString -> ByteString
- strictTextToLazyText :: Text -> Text
- lazyTextToStrictText :: Text -> Text
- strToStrictByteString :: String -> ByteString
- strToLazyByteString :: String -> ByteString
- ppad :: Show a => [[a]] -> [[[Char]]]
- jsonDecode :: FromJSON a => String -> Maybe a
- jsonToRecord :: FromJSON a => FilePath -> IO (Maybe a)
- compileJava :: FilePath -> IO ExitCode
- pm :: Show a => String -> [[a]] -> IO ()
- pls :: [String] -> IO ()
- ps :: String -> IO ()
- printMat :: Show a => [[a]] -> IO ()
- pmat :: Show a => [[a]] -> IO ()
- pMat :: Show a => [[a]] -> IO ()
- matrixToStr :: Show a => [[a]] -> [String]
- psTab :: Integer -> String -> IO ()
- pa :: Show a => [[a]] -> IO ()
- paa :: Show a => [[a]] -> IO ()
- listSlide :: [a] -> Int -> [[a]]
- partList :: Int -> [a] -> [[a]]
- partList2_delete :: Int -> [a] -> [[a]]
- partListDiff :: Int -> Int -> [a] -> [[a]]
- getLineX :: IO String
- copyFileX :: FilePath -> FilePath -> IO ()
- cp :: FilePath -> FilePath -> IO ()
- spanA :: (a -> Bool) -> [a] -> ([a], [a])
- splitSPC :: String -> [String]
- splitBlock :: [String] -> String -> [[String]]
- parseFileBlock :: String -> String -> [String] -> [(Integer, [String])]
- prefix :: String -> [String]
- prefixSuffix :: String -> [String]
- lengthK :: Int -> String -> [String]
- substr :: Int -> String -> [[String]]
- allSubstr :: String -> [[String]]
- unique :: Ord a => [a] -> [a]
- uniqueOrder :: Ord a => [a] -> [a]
- mergeListList :: [[String]] -> [[String]] -> [[String]]
- mergeList :: [a] -> [a] -> [a]
- mergeListLen :: [a] -> [a] -> Maybe [a]
- mergeSortList :: Ord a => [a] -> [a] -> [a]
- iterateList :: [a] -> (a -> IO ()) -> IO ()
- unwrap :: Maybe a -> a
- codeCapture :: String -> String
- binarySearch :: Ord a => a -> [a] -> Bool
- qqsort :: (a -> a -> Bool) -> [a] -> [a]
- sort :: Ord a => [a] -> [a]
- sqVec :: Ord a => Vector a -> Vector a
- quickSort :: [Int] -> [Int]
- quickSort' :: [Int] -> [Int]
- quickSort1 :: Ord a => [a] -> [a]
- quickSortAny :: Ord a => [a] -> [a]
- mergeSortedList :: Ord a => [a] -> [a] -> [a]
- rotateRight :: Integer -> [a] -> [a]
- rotateLeft2 :: [[a]] -> [[a]]
- rotateRight2 :: [[a]] -> [[a]]
- rotateLeft :: Integer -> [a] -> [a]
- mergeSortC :: (a -> a -> Bool) -> [a] -> [a]
- mergeSort :: [Int] -> [Int]
- mergeSortM :: (Num a, Eq a) => [[a]] -> [[a]]
- groupCount :: [String] -> [(String, Integer)]
- vimLink :: IO ()
- watchDir :: FilePath -> IO Bool
- fileModTime :: FilePath -> IO EpochTime
- fileModTimeInt :: FilePath -> IO Int
- fileModTimeInteger :: FilePath -> IO Integer
- intToCTime :: Int -> CTime
- dirModified :: FilePath -> IO [EpochTime]
- fileSizeA :: FilePath -> IO Integer
- readSnippet :: FilePath -> IO [([String], [String])]
- readSnippetStr :: FilePath -> IO [(String, String)]
- readSnippetToDatabase :: FilePath -> Connection -> IO ()
- queryDatabaseToFile :: FilePath -> Connection -> IO ()
- mysqlQuery :: IO ()
- createConfigMap :: [[(String, String)]] -> HashMap String (HashMap String String)
- readFileRemote :: FilePath -> FilePath -> IO ()
- readFileRemoteToList :: FilePath -> IO ByteString
- readFileLatin1 :: FilePath -> IO String
- readFile2d :: Read a => FilePath -> IO [[a]]
- readFileToInteger2d :: FilePath -> IO [[Integer]]
- orgList :: [String] -> [String]
- orgTable :: FilePath -> [[String]] -> IO ()
- writeToFile :: FilePath -> [String] -> IO ()
- writeFileBS :: FilePath -> ByteString -> IO ()
- writeFileListBS :: FilePath -> [ByteString] -> IO ()
- writeToFileAppend :: FilePath -> [String] -> IO ()
- writeFileListAppend :: FilePath -> [String] -> IO ()
- nToFractMat :: (Real a, Fractional b) => [[a]] -> [[b]]
- toNum :: Num a => Integer -> a
- nToNumMat :: Num b => [[Integer]] -> [[b]]
- rToRatMat :: Real a => [[a]] -> [[Rational]]
- writeToFile2dMat :: (Num a, Fractional a, Show a) => FilePath -> [[a]] -> IO ()
- writeToFileMat :: FilePath -> [[String]] -> IO ()
- filtermap :: (a -> Maybe b) -> [a] -> [b]
- putStrLnBS :: ByteString -> IO ()
- putStrBS :: ByteString -> IO ()
- bs :: [[Double]] -> [Double] -> [Double] -> [Double]
- fs :: [[Double]] -> [Double] -> [Double] -> [Double]
- listDot :: Num a => [a] -> [a] -> a
- listDots :: Num a => [[a]] -> [[a]] -> a
- scaleList :: Num a => a -> [a] -> [a]
- listScale :: Num a => [a] -> a -> [a]
- listAdd :: Num a => [a] -> [a] -> [a]
- listSub :: Num a => [a] -> [a] -> [a]
- listMul :: Num a => [a] -> [a] -> [a]
- listNeg :: Num a => [a] -> [a]
- dim :: [[a]] -> (Int, Int)
- zipWithArr :: Num a => (a -> a -> a) -> IOArray Int a -> IOArray Int a -> IO (IOArray Int a)
- zipWithArrToList :: Num a => (a -> a -> a) -> IOArray Int a -> IOArray Int a -> IO [a]
- det :: Num a => [[a]] -> a
- multiMatInt :: [[Int]] -> [[Int]] -> [[Int]]
- multiVec :: Num a => [[a]] -> [a] -> [[a]]
- multiVecL :: Num a => [[a]] -> [a] -> [a]
- multiMatStr :: [[String]] -> [[String]] -> [[String]]
- cart :: [[a]] -> [[a]] -> [[([a], [a])]]
- multiMatDouble :: [[Double]] -> [[Double]] -> [[Double]]
- multiMatR :: [[Rational]] -> [[Rational]] -> [[Rational]]
- multiMatNum :: Num a => [[a]] -> [[a]] -> [[a]]
- multiMat :: Num a => [[a]] -> [[a]] -> [[a]]
- matDiv :: [[Integer]] -> Integer -> [[Integer]]
- multiRatMat :: [[String]] -> [[String]] -> [[String]]
- sumRatList :: [String] -> String
- addR :: String -> String -> String
- matId :: Num a => Int -> [[a]]
- matZero :: Num a => Int -> [[a]]
- ratToInt :: String -> String
- normalR :: String -> String
- reduceForm :: [[String]] -> [[String]]
- reduce :: [Integer] -> [Integer]
- stringToFloat :: String -> Float
- strToF :: String -> Float
- stringToListInt :: String -> [Int]
- word :: String -> (String, String)
- sentence :: String -> [String]
- isWord :: String -> Bool
- isInWord :: Char -> Bool
- hasWordChar :: String -> Bool
- isZeroPos :: String -> Bool
- perm :: [a] -> [[[a]]]
- perm2 :: Eq a => [a] -> [[a]]
- rangeNum :: Eq a => Integer -> [a] -> [[a]]
- perm3 :: [a] -> [[a]]
- splitR :: String -> [Integer]
- multR :: String -> String -> String
- multRL :: String -> [String] -> [String]
- normR :: [String] -> [String] -> String
- getVec :: Int -> [[a]] -> [[a]]
- normList :: Floating a => [[a]] -> [[a]]
- proj :: [String] -> [String] -> [String]
- projn :: Fractional a => [[a]] -> [[a]] -> [[a]]
- rMatrixUpperTri :: Num c => [[[c]]] -> [[[c]]] -> [[c]]
- rejection :: Fractional a => [[[a]]] -> [[[a]]] -> [[[a]]]
- qrDecompose' :: [[Double]] -> ([[Double]], [[Double]])
- addRL :: [String] -> [String] -> [String]
- divR :: String -> String -> String
- divR' :: Integer -> Integer -> String
- invR :: String -> String
- subR :: String -> String -> String
- negR :: String -> String
- negList :: [String] -> [String]
- subRL :: [String] -> [String] -> [String]
- eightQueen :: [[Integer]] -> [(Integer, Integer)] -> Integer -> Integer -> [[Integer]]
- sumLeft :: [[Integer]] -> Integer -> Integer -> Integer
- sumRight :: [[Integer]] -> Integer -> Integer -> Integer
- rep2d :: (Integral n1, Integral n2) => [[a]] -> n1 -> n2 -> a -> [[a]]
- replace1d :: Int -> (a -> a) -> [a] -> [a]
- replace2d :: a -> (Int, Int) -> [[a]] -> [[a]]
- diag1 :: Num a => [[a]] -> [a]
- uptri :: [[a]] -> [[a]]
- leftDiagonal :: [[Integer]] -> Integer -> Integer -> [Integer]
- rightDiagonal :: [[Integer]] -> Integer -> Integer -> [Integer]
- reverseWord :: String -> String
- rw :: String -> String
- tran :: [[a]] -> [[a]]
- sortRow :: [[Integer]] -> [[Integer]]
- upperTri :: [[Integer]] -> [[Integer]]
- upperTri' :: [[Rational]] -> [[Rational]]
- divI :: Fractional a => Integer -> Integer -> a
- inverse :: [[Double]] -> ([[Double]], [[String]])
- odds :: [a] -> [a]
- evens :: [a] -> [a]
- isInver :: (Fractional a, Ord a) => [[a]] -> Bool
- isInvertible :: [[Integer]] -> Bool
- ident :: Integer -> [[Integer]]
- ident' :: Num a => Int -> [[a]]
- identS :: Integer -> [[String]]
- mlist :: Integer -> [Integer] -> [Integer]
- randomTemp :: IO String
- drawInteger :: Integer -> Integer -> IO Int
- randomInteger :: Integer -> Integer -> IO Integer
- randomDouble :: Int -> IO [Double]
- randomFloat :: Int -> IO [Float]
- randomFrac :: Fractional a => Int -> IO [a]
- randomList :: Integer -> IO [Integer]
- randIntList :: Int -> (Int, Int) -> IO [Int]
- randomIntList :: Int -> (Int, Int) -> IO [Int]
- randomIntegerList :: Integer -> (Integer, Integer) -> IO [Integer]
- randomMatrix :: Num a => Int -> Int -> IO [[a]]
- geneRandMat :: Num a => (Int, Int) -> IO [[a]]
- data Mat
- geneMat1ToN :: Num a => Integer -> [[a]]
- geneMatMN :: Integer -> Integer -> [[Integer]]
- geneMat :: Integer -> Mat -> [[Integer]]
- help :: IO ()
- cmd :: [String] -> IO ()
- compileHaskellToBin :: String -> String -> IO ()
- strCompareIC :: String -> String -> Bool
- baseName :: FilePath -> String
- dropExt :: FilePath -> String
- takeExt :: FilePath -> String
- takeName :: FilePath -> String
- dropName :: FilePath -> FilePath
- takeDir :: FilePath -> FilePath
- dropNameT :: Text -> Text
- dropExtT :: Text -> Text
- baseNameT :: Text -> Text
- takeFileNameT :: Text -> Text
- gotoCurrDir :: IO ()
- dirWalk :: FilePath -> (FilePath -> IO [String]) -> IO [String]
- dirWalkPathList :: (FilePath -> IO [String]) -> [FilePath] -> IO [String]
- lsCurr :: String -> IO [String]
- lsDir :: FilePath -> IO [FilePath]
- getDirContent :: FilePath -> IO [FilePath]
- lsRegex :: String -> RegexStr -> IO [String]
- touch :: FilePath -> IO ()
- rm :: FilePath -> IO ()
- isDir :: FilePath -> IO Bool
- dirExist :: FilePath -> IO Bool
- isFile :: FilePath -> IO Bool
- fExist :: FilePath -> IO Bool
- fileExistA :: FilePath -> IO Bool
- doesExistF :: FilePath -> IO Bool
- fe :: FilePath -> IO Bool
- rmDir :: FilePath -> IO ()
- pwd :: IO ()
- cd :: FilePath -> IO ()
- setCurrentDir :: FilePath -> IO ()
- en :: String -> IO String
- cc :: String -> IO ()
- g :: IO ()
- sleepSec :: Int -> IO ()
- sleep :: Int -> IO ()
- asplitPath :: FilePath -> [String]
- splitPathA :: FilePath -> [FilePath]
- take' :: Integral n => n -> [a] -> [a]
- takeIf :: (a -> Bool) -> [a] -> [a]
- dropIf :: (a -> Bool) -> [a] -> [a]
- takeN :: Integral n => n -> [a] -> [a]
- drop' :: Integral n => n -> [a] -> [a]
- pathBase :: FilePath -> FilePath
- dropPath :: Integer -> String -> String
- dropPathEnd :: Integer -> String -> String
- takePath :: Integer -> String -> String
- takePathEnd :: Integer -> String -> String
- copyRename :: FilePath -> String -> IO ()
- copyFileToDir :: FilePath -> FilePath -> IO ()
- createFile :: FilePath -> IO ()
- listDirFilter :: FilePath -> String -> IO [FilePath]
- lsFileFilter :: FilePath -> String -> IO [FilePath]
- copyDir :: FilePath -> FilePath -> IO ()
- mv :: FilePath -> FilePath -> IO ()
- rename :: FilePath -> FilePath -> IO ()
- renameAllFile :: String -> String -> IO ()
- mvFiles :: String -> String -> IO ()
- mvFile :: FilePath -> FilePath -> IO ()
- mkdir :: FilePath -> IO ()
- mkdirp :: FilePath -> IO ()
- sfilter :: String -> [String] -> [String]
- setCursorPos :: Int -> Int -> IO ()
- setCursorPosStr :: Int -> Int -> String
- getTerminalSize :: IO (Int, Int)
- getScreenSize :: IO (Int, Int)
- sys :: String -> IO ExitCode
- typeChar :: Typeable a => a -> Bool
- linesBS :: ByteString -> [ByteString]
- linesSText :: Text -> [Text]
- linesST :: Text -> [Text]
- isHex :: Char -> Bool
- isHexStr :: String -> Bool
- isDigitStr :: String -> Bool
- isLetterStr :: String -> Bool
- isLetterChar :: Char -> Bool
- isDigitChar :: Char -> Bool
- run' :: String -> IO ()
- run :: String -> IO [String]
- runCmd :: String -> IO [String]
- runShell :: String -> IO (ExitCode, Text, Text)
- df :: Fractional a => (a -> a) -> a -> a
- tangent :: Fractional a => (a -> a) -> a -> a -> a
- tangentVec :: Fractional a => (a -> a) -> a -> a -> (a, a)
- prime :: [Integer]
- oneRoot :: (Double -> Double) -> Double -> Double -> Double -> Maybe Double
- rootList :: (Double -> Double) -> Double -> Double -> Double -> Integer -> [Maybe Double]
- outer :: Num a => [a] -> [a] -> [[a]]
- out :: (a -> b -> c) -> [a] -> [b] -> [[c]]
- outerSum :: Num a => [a] -> [a] -> [[a]]
- outerMod :: Integral a => [a] -> [a] -> [[a]]
- outerStr :: (a -> a -> a) -> [[a]] -> [[a]] -> [[a]]
- (⦶) :: Integral a => [a] -> [a] -> [[a]]
- (‖) :: Integer -> Integer -> Integer
- vcol :: [[a]] -> Int -> [[a]]
- getColumn :: [[a]] -> Int -> [[a]]
- vrow :: [[a]] -> Int -> [[a]]
- getRow :: [[a]] -> Int -> [[a]]
- zipWith2 :: Num a => (a -> a -> a) -> [[a]] -> [[a]] -> [[a]]
- data XNode = XNode (HashMap Char XNode) Bool
- insertTries :: String -> XNode -> XNode
- insertTriesList :: [String] -> XNode -> XNode
- containsTries :: String -> XNode -> Bool
- data Tree a
- insertNode :: Ord a => Tree a -> a -> Tree a
- insertFromList :: Ord a => Tree a -> [a] -> Tree a
- data LeafyTree a
- inorder :: Tree a -> [a]
- maxlen :: Tree a -> Integer
- head' :: [a] -> a
- isBST :: Ord a => Tree a -> Bool
- binsert :: Tree Integer -> Tree Integer -> Tree Integer
- isSym :: Tree a -> Bool
- lca :: Eq a => Tree a -> a -> a -> Maybe a
- buildTree :: [Char] -> [Char] -> Tree Char
- anagram :: String -> [String] -> [String]
- redisExtractAronModule :: String -> [String] -> [([String], Integer, [String])]
- redisExtractJavaMethod :: String -> [String] -> [([String], Integer, [String])]
- redisExtractJavaMethodWithPackage :: String -> [String] -> [([String], Integer, [String])]
- redisExtractSnippet :: [([String], [String])] -> [([String], Integer, [String])]
- textArea :: Integer -> Integer -> String -> String
- htmlTable :: [[String]] -> [String]
- htmlTableRowCol :: Int -> Int -> [String]
- htmlTableRowColSText :: Integer -> Integer -> [Text]
- getOS :: IO String
- data ShellHistory = ShellHistory {}
- insertShellHistory :: String -> String -> IO ()
- queryShellHistory :: String -> IO [String]
- appNotify :: String -> IO ()
- redisGet :: String -> IO (Maybe String)
- redisGetConn :: Connection -> String -> IO (Maybe String)
- redisSet :: String -> String -> IO ()
- redisSetConn :: Connection -> String -> String -> IO ()
- redisSetConnSByteString :: Connection -> ByteString -> ByteString -> IO ()
- redisConnectDefault :: IO Connection
- redisDisconnect :: Connection -> IO ()
- checkCSSColorFormat :: Text -> Bool
- cssToStr :: (String, String) -> String
- concatStyle :: [(String, String)] -> String
- fun444 :: Int -> Int
- fun555 :: Int -> Int
- pf :: PrintfType r => String -> r
- p :: Show s => s -> IO ()
- pp2 :: (MonadIO m, Show a) => a -> m ()
- fl :: IO ()
- pw :: Show s => String -> s -> IO ()
- fpp :: Show s => String -> s -> IO ()
- fw :: String -> IO ()
- ff :: Show var => String -> var -> IO ()
- (?) :: Bool -> a -> a -> a
- (<<<) :: Show a => String -> a -> String
- readConfig :: FilePath -> IO (HashMap String (HashMap String String))
- concatFile :: FilePath -> FilePath -> FilePath -> IO ()
- extractNumFromStr :: String -> Integer
- strToIntegerMaybe :: String -> Maybe Integer
- gcdList :: [Integer] -> Integer
- commentLine :: String -> String -> String
- commentCode :: String -> [String] -> [String]
- takeBetweenExc :: String -> String -> [String] -> [String]
- takeIndexBetweenInc :: (Int, Int) -> [a] -> [a]
- maxList :: [Int] -> Int
- printBox :: Integer -> [String] -> IO ()
- printBoxColor :: Color -> Integer -> [String] -> IO ()
- printBoxColor2 :: Integer -> Integer -> [String] -> IO ()
- splitWhileStr :: (Char -> Bool) -> String -> (String, String)
- getLineFlush :: IO String
- replaceFileLineNoRegex :: FilePath -> String -> String -> IO ()
- replaceLineNoRegexListTuple :: [String] -> [(String, String)] -> [String]
- runSh :: Text -> IO (ExitCode, Text, Text)
- runShStr :: String -> IO (ExitCode, String, String)
- clear :: IO ()
- pp :: Show s => s -> IO ()
- runRawCmd :: String -> [String] -> IO [String]
- ls :: IO ()
- getPwd :: IO FilePath
- getpwd :: IO FilePath
- lsFile :: String -> IO [String]
- lsStr :: String -> IO [String]
- drawInt :: Int -> Int -> IO Int
- lsFileFull :: String -> IO [String]
- type RegexStr = String
- lsRegexFull :: String -> RegexStr -> IO [String]
- lsFullRegex :: String -> RegexStr -> IO [String]
- randomInt :: Int -> Int -> IO Int
- writeFileStr :: FilePath -> String -> IO ()
- writeFileOver :: FilePath -> String -> IO ()
- writeFileList :: FilePath -> [String] -> IO ()
- c2w_ :: Char -> Word8
- intToString :: Integer -> String
- integerToString :: Integer -> String
- integerToInt :: Integer -> Int
- intToCharDigit :: Int -> Char
- extractStr :: (Integer, Integer) -> String -> String
- integerToBinary :: Integer -> String
- charToDecimal :: Char -> Int
- charToDecimalInteger :: Char -> Integer
- charToIntX :: Char -> Int
- char0to9ToInt :: Char -> Int
- integerToCharDigit :: Integer -> Char
- stringToInteger :: String -> Integer
- strToInteger :: String -> Integer
- stringToInt :: String -> Int
- strToInt :: String -> Int
- pre :: (MonadIO m, Show a) => a -> m ()
- prex :: (MonadIO m, Show a) => a -> m ()
- prel :: Show a => [[a]] -> IO ()
- readFileLatin1ToList :: FilePath -> IO [String]
- readFileList :: FilePath -> IO [String]
- readFileStr :: FilePath -> IO String
- readFileDouble :: FilePath -> IO [[Double]]
- readFileFloat :: FilePath -> IO [[Float]]
- readFileInt :: FilePath -> IO [[Int]]
- timeNowPico :: IO Integer
- timeNowNano :: IO Integer
- timeNowMicro :: IO Integer
- timeNowMilli :: IO Integer
- timeNowSecond :: IO Integer
- timeNowSec :: IO Integer
- getLocalTime :: IO LocalTime
- getLocalDate :: IO String
- getDate :: IO String
- dateStr :: IO String
- date :: IO ()
- getTime :: IO String
- showTime :: IO ()
- trim :: String -> String
- splitStr :: RegexStr -> String -> [String]
- splitStrChar :: RegexStr -> String -> [String]
- splitStrCharTrim :: RegexStr -> String -> [String]
- matchAllBS :: ByteString -> ByteString -> [(MatchOffset, MatchLength)]
- len :: (Foldable t, Num b) => t a -> b
- splitStrTuple :: String -> String -> (String, String)
- logFile :: FilePath -> [String] -> IO ()
- logFile2 :: FilePath -> [String] -> IO ()
- logFileTmp :: [String] -> IO ()
- logFileNoName :: [String] -> IO ()
- logFileGEx :: Bool -> String -> [String] -> IO ()
- logFileG :: [String] -> IO ()
- logFileGT :: String -> [String] -> IO ()
- logFileMat :: Show a => String -> [[a]] -> IO ()
- logFileSBS2 :: FilePath -> [ByteString] -> IO ()
- showIntAtBaseX :: Integral a => a -> (Int -> Char) -> a -> ShowS
- integerToHex :: Integer -> String
- intToHex :: Integer -> String
- hexToInt :: String -> Integer
- unescape :: String -> String
- intToUnicode :: Int -> Char
- hexToUnicode :: String -> Char
- intToChar :: Int -> Char
- hexToChar :: String -> Char
- ρ :: [a] -> Int
- data FrameCount = FrameCount {
- frameTime :: Integer
- frameCount :: Integer
- frameNewCount :: Integer
- frameIndex :: Int
- resetRefFrame :: IORef FrameCount -> IO ()
- readRefFrame2 :: IORef FrameCount -> Integer -> IO (Int, Bool, FrameCount)
- fileSizeStrToNum :: String -> Float
- whichGetPath :: String -> IO FilePath
- openFileUtf8 :: MonadIO m => FilePath -> IOMode -> m Handle
- readFileUtf8 :: MonadIO m => FilePath -> m Text
- scientificToFloat :: RealFloat a => Int -> a -> String
- sciToFloat :: RealFloat a => Int -> a -> String
- colorfgStr :: Integer -> String -> String
- colorbgStr :: Int -> String -> String
- createProcessPipeData :: String -> [String] -> String -> IO (Maybe Handle, ExitCode)
- writeFileSText :: FilePath -> Text -> IO ()
- writeFileLText :: FilePath -> Text -> IO ()
- pad :: Num a => Int -> a -> [a] -> [a]
- nzero :: Num a => Int -> [a]
- shiftMatrixLeft :: Num a => Int -> [[a]] -> [[a]]
- shellHighlight :: String -> [String]
- blockBegEnd :: (String -> Bool) -> (String -> Bool) -> [String] -> [[String]]
- pick :: (a -> Bool) -> [a] -> ([a], [a])
- containAll :: Ord a => [a] -> [a] -> Bool
- combin :: Int -> [a] -> [[a]]
- drawRectBar :: (Pixel px, PrimMonad m) => MutableImage (PrimState m) px -> (Int, Int) -> (Int, Int) -> Int -> [Int] -> px -> m ()
- histogram :: FilePath -> IO ()
- insertIndexAt :: Int -> a -> [a] -> [a]
- isInList :: String -> [String] -> Bool
- removeFirstList :: Ord a => a -> [a] -> [a]
- removeFromList :: Ord a => a -> [a] -> [a]
- readFileInteger2d :: FilePath -> IO [[Integer]]
- readFileFloat2d :: FilePath -> IO [[Float]]
- readTable :: FilePath -> IO [[String]]
- alignTable :: [String] -> [[String]]
- columnTable :: [String] -> [[String]]
- trimList :: [String] -> [String]
- trimListST :: [Text] -> [Text]
- stepList :: [a] -> Int -> [([a], [Int])]
- splitWhenFirstNoRegex :: String -> String -> Maybe (String, String)
- splitWhenLastNoRegex :: String -> String -> Maybe (String, String)
- splitStrCharNoRegex :: String -> String -> [String]
- printFile :: FilePath -> IO ()
- frequenceCount :: Ord a => [a] -> [(a, Int)]
- data FileBlock
- = DropHead
- | DropLast
- | DropIndex Int
- | PrintIndex Int
- | PrintHead
- | PrintLast
- | PrintAll
- | Append String
- | AppendList [String]
- | Prepend String
- | NumberOfBlock
- fileBlock :: FilePath -> String -> FileBlock -> IO ()
- splitPrefix :: (a -> Bool) -> [a] -> ([a], [a])
- breakFirst :: (a -> Bool) -> [a] -> ([a], [a])
- grepx :: ByteString -> FilePath -> IO ()
- grepLine :: FilePath -> (String -> Bool) -> IO ()
- catx :: FilePath -> IO ()
- clipBoardcp :: String -> IO ()
- pbcopy :: String -> IO ()
- clipBoardpa :: IO [String]
- pbpaste :: IO [String]
- getContentsCTRLD :: IO String
- hasSubstr :: String -> String -> Bool
- hasStrBlock :: String -> [String] -> [[String]]
- powerSet :: [a] -> [[a]]
- swap :: (Int, Int) -> [a] -> [a]
- printMat3 :: Show a => IOArray (Int, Int, Int) a -> IO ()
- printMat2 :: Show a => IOArray (Int, Int) a -> IO ()
- cap :: IO a -> IO String
- readAndParse :: Read a => FilePath -> IO a
- readMaybeParse :: Read a => FilePath -> IO (Maybe a)
- multiMatArr :: (Ix a, Ix b, Ix c, Num n) => Array (a, b) n -> Array (b, c) n -> Array (a, c) n
- compareArray :: [Int] -> [Int] -> Int
Documentation
print_ascii_c :: IO () Source #
How to build AronModule.hs | ghc --make AronModule.hs
Strict ByteString Char8 Strict ByteString UTF8 Lazy ByteString Char8 <http://hackage.haskell.org/package/utf8-string-1.0.1.1/docs/Data-ByteString-Lazy-UTF8.html Lazy ByteString UTF8
- KEY: haskell ffi, c function SEE: UsersaaamyfilebitbuckethaskellffiAronCLibFFI.c
print_ascii_f :: IO () Source #
- KEY: haskell ffi, c function SEE: UsersaaamyfilebitbuckethaskellffiAronCLibFFI.c
Overloading the sin, cos to avoid Haskell crazy strict type | TODO: add test cases
No much to say
- Division is painful in Haskell
- Try to overload _div for many types
- TODO: add more combination?
- TODO: add test cases
define record for all the code blocks can not define [TS.Text] => sqlite3 does not support [TS.Text]
data SqliteMaster Source #
SqliteMaster | |
|
Instances
Eq SqliteMaster Source # | |
Defined in AronModule (==) :: SqliteMaster -> SqliteMaster -> Bool (/=) :: SqliteMaster -> SqliteMaster -> Bool | |
Read SqliteMaster Source # | |
Defined in AronModule readsPrec :: Int -> ReadS SqliteMaster readList :: ReadS [SqliteMaster] readPrec :: ReadPrec SqliteMaster readListPrec :: ReadPrec [SqliteMaster] | |
Show SqliteMaster Source # | |
Defined in AronModule showsPrec :: Int -> SqliteMaster -> ShowS show :: SqliteMaster -> String showList :: [SqliteMaster] -> ShowS | |
FromRow SqliteMaster Source # | |
Defined in AronModule fromRow :: RowParser SqliteMaster | |
ToRow SqliteMaster Source # | |
Defined in AronModule toRow :: SqliteMaster -> [SQLData] |
data UpdateCodeBlock Source #
Instances
Show UpdateCodeBlock Source # | |
Defined in AronModule showsPrec :: Int -> UpdateCodeBlock -> ShowS show :: UpdateCodeBlock -> String showList :: [UpdateCodeBlock] -> ShowS | |
Generic UpdateCodeBlock Source # | |
Defined in AronModule type Rep UpdateCodeBlock :: Type -> Type from :: UpdateCodeBlock -> Rep UpdateCodeBlock x to :: Rep UpdateCodeBlock x -> UpdateCodeBlock | |
FromJSON UpdateCodeBlock Source # | |
Defined in AronModule parseJSON :: Value -> Parser UpdateCodeBlock parseJSONList :: Value -> Parser [UpdateCodeBlock] | |
ToJSON UpdateCodeBlock Source # | |
Defined in AronModule toJSON :: UpdateCodeBlock -> Value toEncoding :: UpdateCodeBlock -> Encoding toJSONList :: [UpdateCodeBlock] -> Value toEncodingList :: [UpdateCodeBlock] -> Encoding | |
type Rep UpdateCodeBlock Source # | |
Defined in AronModule type Rep UpdateCodeBlock = D1 ('MetaData "UpdateCodeBlock" "AronModule" "main" 'False) (C1 ('MetaCons "UpdateCodeBlock" 'PrefixI 'True) ((S1 ('MetaSel ('Just "pid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "newcode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :*: (S1 ('MetaSel ('Just "begt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "endt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))) |
data UpdateCodeBlockX Source #
Instances
Show UpdateCodeBlockX Source # | |
Defined in AronModule showsPrec :: Int -> UpdateCodeBlockX -> ShowS show :: UpdateCodeBlockX -> String showList :: [UpdateCodeBlockX] -> ShowS | |
Generic UpdateCodeBlockX Source # | |
Defined in AronModule type Rep UpdateCodeBlockX :: Type -> Type from :: UpdateCodeBlockX -> Rep UpdateCodeBlockX x to :: Rep UpdateCodeBlockX x -> UpdateCodeBlockX | |
FromJSON UpdateCodeBlockX Source # | |
Defined in AronModule parseJSON :: Value -> Parser UpdateCodeBlockX parseJSONList :: Value -> Parser [UpdateCodeBlockX] | |
ToJSON UpdateCodeBlockX Source # | |
Defined in AronModule toJSON :: UpdateCodeBlockX -> Value toEncoding :: UpdateCodeBlockX -> Encoding toJSONList :: [UpdateCodeBlockX] -> Value toEncodingList :: [UpdateCodeBlockX] -> Encoding | |
type Rep UpdateCodeBlockX Source # | |
Defined in AronModule type Rep UpdateCodeBlockX = D1 ('MetaData "UpdateCodeBlockX" "AronModule" "main" 'False) (C1 ('MetaCons "UpdateCodeBlockX" 'PrefixI 'True) ((S1 ('MetaSel ('Just "pidx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "pidlistx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Integer])) :*: (S1 ('MetaSel ('Just "newcodex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "begtx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "endtx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer))))) |
data CodeBlockReply Source #
Instances
Show CodeBlockReply Source # | |
Defined in AronModule showsPrec :: Int -> CodeBlockReply -> ShowS show :: CodeBlockReply -> String showList :: [CodeBlockReply] -> ShowS | |
Generic CodeBlockReply Source # | |
Defined in AronModule type Rep CodeBlockReply :: Type -> Type from :: CodeBlockReply -> Rep CodeBlockReply x to :: Rep CodeBlockReply x -> CodeBlockReply | |
FromJSON CodeBlockReply Source # | |
Defined in AronModule parseJSON :: Value -> Parser CodeBlockReply parseJSONList :: Value -> Parser [CodeBlockReply] | |
ToJSON CodeBlockReply Source # | |
Defined in AronModule toJSON :: CodeBlockReply -> Value toEncoding :: CodeBlockReply -> Encoding toJSONList :: [CodeBlockReply] -> Value toEncodingList :: [CodeBlockReply] -> Encoding | |
type Rep CodeBlockReply Source # | |
Defined in AronModule type Rep CodeBlockReply = D1 ('MetaData "CodeBlockReply" "AronModule" "main" 'False) (C1 ('MetaCons "CodeBlockReply" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ok") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "retcmd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :*: (S1 ('MetaSel ('Just "retdata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "retbegt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "retendt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer))))) |
Instances
Show ReplyCode Source # | |
Generic ReplyCode Source # | |
FromJSON ReplyCode Source # | |
Defined in AronModule parseJSON :: Value -> Parser ReplyCode parseJSONList :: Value -> Parser [ReplyCode] | |
ToJSON ReplyCode Source # | |
Defined in AronModule toEncoding :: ReplyCode -> Encoding toJSONList :: [ReplyCode] -> Value toEncodingList :: [ReplyCode] -> Encoding | |
type Rep ReplyCode Source # | |
Defined in AronModule type Rep ReplyCode = D1 ('MetaData "ReplyCode" "AronModule" "main" 'False) (C1 ('MetaCons "ReplyCode" 'PrefixI 'True) (S1 ('MetaSel ('Just "rcmd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "rerror") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "stdoutx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) |
data CommandService Source #
Instances
Show CommandService Source # | |
Defined in AronModule showsPrec :: Int -> CommandService -> ShowS show :: CommandService -> String showList :: [CommandService] -> ShowS | |
Generic CommandService Source # | |
Defined in AronModule type Rep CommandService :: Type -> Type from :: CommandService -> Rep CommandService x to :: Rep CommandService x -> CommandService | |
FromJSON CommandService Source # | |
Defined in AronModule parseJSON :: Value -> Parser CommandService parseJSONList :: Value -> Parser [CommandService] | |
ToJSON CommandService Source # | |
Defined in AronModule toJSON :: CommandService -> Value toEncoding :: CommandService -> Encoding toJSONList :: [CommandService] -> Value toEncodingList :: [CommandService] -> Encoding | |
type Rep CommandService Source # | |
Defined in AronModule type Rep CommandService = D1 ('MetaData "CommandService" "AronModule" "main" 'False) (C1 ('MetaCons "CommandService" 'PrefixI 'True) (S1 ('MetaSel ('Just "cmdServ") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "paramArg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "inputData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) |
divInteger :: Integer -> Integer -> Double Source #
divII :: (Num a, Fractional a) => Integer -> Integer -> a Source #
Num => a ring
- Addition
- Addition inverse
- Multiplcation
- Multiplcation identity
- Associativity
- Distribution over multiplication
class Num a where (+):: a -> a -> a (-)::a -> a -> a (*)::a -> a -> a abs:: a -> a negate::a -> a signum::a -> a fromIntegral Integer -> a
- Fractional => field class Num a => Fractional a where (/)::a -> a -> a recip :: a -> a fromRational :: Rational -> a
redisBound :: RedisGroup -> Integer Source #
loge :: Double -> Double Source #
approximate nature log function with Integral function
\[ \log_e x = \int_{1}^{x} \frac{d t}{t} \]
- Partition the interval \( x \gt 1, [1, x] \text{ or } x \lt 1, [x, 1] \) to \( n = 100 \)
- Compute each step value on x-axis \( 1 + \frac{k - 1}{n}, k \gt 1 \) or \( \frac{1 - k}{n} - 1, k < 1\)
- Compute the average hight of \( \frac{1}{x} \) between \( x_{i}, x_{i+1} \), \( h_i = \frac{f (x_i) + f(x_{i+1})}{2} \)
- The width of each step is \( w = (k - 1) \times \frac{1}{n} \)
- Each \(i\) rectangle area is \( w \times h_i \)
- Total area of all rectanges are \( \sum_{i=1}^{n} w \times h_i \)
- NOTE: if \( k \) is close to \( n = 100 \), then \( \log_e \) is not longer accurate value.
- NOTE: There is no rational polynomial to approximate \( \log_e \) in large value in fast speed.
- approximate_log_e
radianToDegree :: Float -> Float Source #
radianToDegree::Float->Float radianToDegree x = x*r where r = 180/pi
degreeToRadian :: Float -> Float Source #
degreeToRadian::Float->Float degreeToRadian x = x*d where d = pi/180
toUpperStr :: String -> String Source #
KEY: upper case string
Same as upperStr
upperStr :: String -> String Source #
KEY: upper case string
Same as toUpperStr
toLowerStr :: String -> String Source #
Lower string
https://hoogle.haskell.org/?hoogle=tolower tolower>
toLowerStr s = foldr(\x y -> (toLower x):y) [] s
concatStr :: [String] -> String -> String Source #
KEY: concat string with delimter string s, concat str, join string
concatStr ["dog", "cat"] [] => "dogcat" concatStr ["dog", "cat"] " " => "dog cat" concatStr ["dog", "cat"] ":" => "dog:cat"
cat :: String -> IO () Source #
KEY: cat string, concat string
cat ["dog", "cat"] => "dogcat"
KEY: cat file, like command line cat
cat "/tmp/x.html"
readDirMatchKey :: FilePath -> String -> String -> IO [(String, String)] Source #
KEY: read file, find pattern, read dir and find pattern, read all keys
p <- getEnv "j" readDirMatchKey p "\\.java$" "KEY:"
[ , ( " KEY: system.in, standard input" , "Userscatmyfilebitbucketjavatry_scanner.java" ) , ( " // KEY: word boundary " , "Userscatmyfilebitbucketjavatry_word_boundary.java" ) ]
containStr :: String -> String -> Bool Source #
Check whether a string p
contains a string s
pattern
- Use regex to check match
"^dog" "dog$" matchTest (mkRegex p) s
containStr "^dog" "dog cat" => True str = "dog cat" p = "dog" containStr p str == return True containStr p s == matchTest (mkRegex p) s
containAscii :: String -> Bool Source #
Check non-ascii char in a string
containNonAsciiList :: [String] -> [(Integer, String)] Source #
Check non-ascii char in a [String]
check file whether it contains non-ASCII char or line
[(Line #, Line)] = [(Integer, String)]
matchAny :: String -> String -> Maybe (Int, Int) Source #
match once string and return Maybe (index, length)
matchAny (mkRegex "dog|cat") "mydog" => Just (2, 3)
See matchOnce
or matchAll
matchAll
matchAnyRegex :: Regex -> String -> Maybe (Int, Int) Source #
match once string and return Maybe (index, length)
matchAnyRegex (mkRegex "dog|cat") "mydog" => Just (2, 3)
See matchOnce
or matchAll
matchAll
matchScore :: SKey -> String -> (Int, String) Source #
matchScoreList :: SKey -> [String] -> [(Int, String)] Source #
fileContainNonAscii :: FilePath -> IO [(Integer, String)] Source #
Check non-ascii char in a file
fileContain :: FilePath -> String -> IO [String] Source #
file has all the lines which contain a pattern
fileHas :: (String -> Bool) -> FilePath -> IO [String] Source #
file has all the lines which contain a pattern
Same as fileContain
filterList :: (Bool -> Bool) -> [String] -> [String] -> [String] Source #
filter out a list of pattern from a list of string
[ mbox{De Morgan's laws: union and intersection} begin{aligned} A ∪ (B ∩ C) &= (A ∩ B) ∪ (A ∩ B) (A ∪ B)^¬ &= A^¬ ∩ B^¬ (A ∩ B)^¬ &= A^¬ ∪ B^¬
end{aligned} ]
- \( A ⊗ B \)
containStr
both "a" \( ⊗ \) "b"
filterList id ["a", "b"] ["aa", "kk", "ab"] ⇒ ["ab"]
containStr
"a"
filterList id ["a"] ["aa", "kk", "ab"] ⇒ ["aa", "ab"]
- \( (A ⊗ B)^¬ = A^¬ ⊕ B^¬ \)
- not
containStr
"a" \( ⊕ \) "b"
filterList not ["a", "b"] ["aa", "bb", "ab"] ⇒ ∅
intersectSet :: (Eq a, Hashable a) => [a] -> [a] -> [a] Source #
diffList :: (Eq a, Hashable a) => [a] -> [a] -> ([a], [a]) Source #
KEY: Difference between two lists
cx = ["a", "b"] cy = ["a", "c"] diffList cx cy => (["b"], ["c"])
interList :: (Eq a, Hashable a) => [a] -> [a] -> [a] Source #
KEY: Intersection between two lists
cx = ["a", "b"] cy = ["a", "c"] diffList cx cy => (["b"], ["c"])
intersectFile :: FilePath -> FilePath -> IO [String] Source #
intersection of two files
filterNonEmpty :: [String] -> [String] Source #
KEY: filter non empty string, no empty line
containPrefix :: String -> String -> Bool Source #
Check whether str contains sub as prefix
containPrefix "dog" "dogcat" => True containPrefix "dog" " dogcat" => False
containSuffix :: String -> String -> Bool Source #
KEY: Check whether str contains sub as suffix
containPrefix "cat" "dogcat" => True containPrefix "cat" "dogcat " => False
hasPrefix :: String -> String -> Bool Source #
KEY: Check whether str has sub as prefix
containPrefix "cat" "dogcat" => True containPrefix "cat" "dogcat " => False
- See
containPrefix
replaceFileLineEscape :: String -> String -> FilePath -> IO [String] Source #
KEY: without any regex substitute,
ISSUE: See replaceFileLine
ISSUE: See replaceList
let sub = "\" -- sub is one character => len sub == 1 pp $ len sub ls <- replaceFileLineEscape "abc" sub "tmp11.x" writeFileList "tmp22.x" ls
replaceFileLineEscapeStrict :: FilePath -> String -> String -> IO [String] Source #
strWithSlash :: String -> String Source #
KEY: string with escape character
ISSUE: See replaceFileLine
replaceList
replaceFileLineEscape
let s = "" let s1 = show "\" let s2 = dropEnd 1 $ drop 1 s1 let s2 = writeFileList "tmpx.x" [s2] -- write s2 to file
replaceFileLine :: String -> String -> FilePath -> IO [String] Source #
KEY: without any regex substitute, remove string and append
ISSUE: See replaceFileLineEscape
ISSUE: See replaceList
let sub = "\" -- sub is one character => len sub == 1 let sub' = dropEnd 1 $ drop 1 $ show sub pp $ len sub ls <- replaceFileLine "abc" sub' "tmp11.x" writeFileList "tmp22.x" ls
redisExtractCppAronLib :: String -> [String] -> [([String], Integer, [String])] Source #
KEY: Generate [([String], Integer, [String])] from captureCppFun
[( [ "AronLib.e" , "AronLib.ew" , "AronLib.ewl" , "AronLib.ewli" , "AronLib.ewlin" , "AronLib.ewline" , "AronLib.i" , "AronLib.in" , "AronLib.ine" , "AronLib.l" , "AronLib.li" , "AronLib.lin" <- [String] , "AronLib.line" , "AronLib.n" , "AronLib.ne" , "AronLib.new" , "AronLib.newl" , "AronLib.newli" , "AronLib.newlin" , "AronLib.newline" , "AronLib.w" , "AronLib.wl" , "AronLib.wli" , "AronLib.wlin" , "AronLib.wline" ] , 40007 <- Integer , [ "void newline(){" ] <- [String] ) ]
[([String], Integer, [String])]
readTagsFile :: FilePath -> IO [(String, String)] Source #
etags -e -f $PWDTAGS $cpplibAronLib.h $bclibAronCLibNew.h ↑ + -> has to be before '-f'
[ ( "string removeIndex(string s, int inx) {" , "removeIndex" ), ( "vectorT removeIndex(vectorT& vec, int inx){" , "removeIndex" ), ( "vectorT removeIndexRange(vectorT& vec, int fromInx, int toInx){" , "removeIndexRange" ) ]
extraTags :: [String] -> [(String, String)] Source #
KEY: extra function from emacs TAGS file
etags -e -f $PWDTAGS $cpplibAronLib.h $bclibAronCLibNew.h ↑ + -> has to be before '-f'
replaceList :: [String] -> String -> String -> [String] Source #
KEY: Replace a matching string with other string
replaceList [" pat ", " pat"] "pat" "sub" ⟹ [" sub ", " sub"]
ERROR: "\" and "\\" with same output
let n = "\" let m = "\\" let n' = subRegex(mkRegex "abc") "abc" n let m' = subRegex(mkRegex "abc") "abc" m pp $ n' == m'
searchSplitAny :: String -> String -> [(String, String, String)] Source #
Search a pattern and partition it three parts: [(String, String, String)]
searchSplitAny "my cat eats my 123 cat" "[[:digit:]]+" [("my cat eats my ","123"," cat")] > searchSplitAny "my cat eats my 123 cat 44a" "[[:digit:]]+" [("my cat eats my ","123"," cat 44a"),(" cat ","44","a")]
searchSplitWord :: String -> String -> [(String, String, String)] Source #
search and replace WORD only
searchSplit "mydog dog-- dog pig cat" "dog" [("my","dog"," dog-- dog pig cat"),(" ","dog","-- dog pig cat"),("-- ","dog"," pig cat")]
searchReplaceAny :: String -> String -> String -> String Source #
KEY: search replace any char, substitude string
- The code is based on
matchAllText
in package:TDFA
as TD
searchReplaceAny "mydog dog-- dog pig cat" "dog" "[\0]" => "my[dog] [dog]-- [dog] pig cat"
- Regex is from TDFA, NOT Text.Regex
word => "[[:alpha:]]+"
- NOTE: support ONE String only, e.g. searchReplace s "dog" "[\0]"
- TODO: support multiple words, e.g. searchReplace s "dog|cat" "[\0]"
See searchReplace
TODO: add test
searchReplaceAnyTup :: String -> (String, String) -> String Source #
searchReplaceAnySBS :: ByteString -> ByteString -> ByteString -> ByteString Source #
searchReplace :: String -> String -> String -> String Source #
Search replace word, the code is based on matchAllText
in package: Text.Regex.TDFA as TD
let s = "mydog dog-- dog pig cat dog fox" searchReplace s "dog" "[\\0]" "mydog [dog]-- [dog] pig cat [dog] fox"
- Text.Regex => subRegex does not support word boundary
r = makeRegex ("\\<" ++ word ++ "\\>")::TD.Regex -- word boundary
- Regex is from TDFA, NOT Text.Regex >word => "[[:alpha:]]+"
- NOTE: support ONE word only, e.g. searchReplace s "dog" "[\0]"
- TODO: support multiple words, e.g. searchReplace s "dog|cat" "[\0]"
See searchReplaceAny
Sun 31 May 13:05:58 2020
1. Fixed bug: if no matches, then the origin string should be returned
2. Moved searchSplit
outside so that searchReplaceAny
can use it.
searchSplit "mydog dog-- dog pig cat" "dog" [("my","dog"," dog-- dog pig cat"),(" ","dog","-- dog pig cat"),("-- ","dog"," pig cat")]
> searchReplace "mydog dog-- dog pig cat" "dog" "[\0]" "mydog [dog]-- [dog] pig cat" > searchReplaceAny "mydog dog-- dog pig cat" "dog" "[\0]" "my[dog] [dog]-- [dog] pig cat" >
searchReplaceWord :: String -> (String, String) -> String Source #
Same as searchReplace
but it is better name
search and replace word
interleave :: [a] -> [a] -> [a] Source #
intersperseInner :: a -> [a] -> [a] Source #
intersperseInner a list
Same as intersperse
from Data.List
intersperseInner "-", [] = [] intersperseInner "-", ["a"] = ["a"] intersperseInner "-", ["a", "b"] = ["a", "-", "b"]
listIn :: a -> [a] -> [a] Source #
Add sth between list
listIn "-", [] = [] listIn "-", ["a"] = ["a"] listIn "-", ["a", "b"] = ["a", "-", "b"]
concat $ listIn "-" ["a", "b"] -- "a-b"
same as intersperseOuter
but it is better name
listOut :: a -> [a] -> [a] Source #
Add sth OVER the list
listOut "-", [] = [] listOut "-", ["a"] = ["-", "a", "-"] listOUt "-", ["a", "b"] = ["-", "a", "-", "b", "-"]
concat $ listOut "-" ["a", "b"] -- "-a-b-"
Same as intersperseInner
but it is better name
intersperseOuter :: a -> [a] -> [a] Source #
intersperseOuter a list
intersperseOuter "-", [] = [] intersperseOuter "-", ["a"] = ["-", "a", "-"] intersperseOuter "-", ["a", "b"] = ["-", "a", "-", "b", "-"]
repeat' :: Integer -> a -> [a] Source #
repeat a n times
repeat' 0 'a' => "" repeat' 0 "a" => [] repeat' 3 'a' => aaa repeat' 3 "a" => ["a", "a", "a"]
- Deprecated
- Use:
repeatN
repeatN :: Integer -> a -> [a] Source #
repeat n times
repeat's 0 'a' => "' repeat's 0 "a" => [] repeat's 3 "pig" => ["pig", "pig", "pig"]
- Use repeatN instead of
repeat
`
replicateN :: Integer -> a -> [a] Source #
repeat n times
repeat's 0 'a' => "' repeat's 0 "a" => [] repeat's 3 "pig" => ["pig", "pig", "pig"]
- same as
replicate
butInteger
type
replicate' :: Int -> a -> [a] Source #
replicate n times
replicate' 4 'a' => "aaaa"
fillList :: Integer -> [Integer] -> [Integer] Source #
fill a list with missing number
fillList 0 [1, 2, 4, 7] [1, 2, 0, 4, 0, 0 7] fillList 0 [-1, 2, 4, 6, 10] [-1,0,0,2,0,4,0,6,0,0,0,10]
pp $ fillList 0 [] == [] pp $ fillList 0 [0] == [0] pp $ fillList 0 [1] == [1] pp $ fillList 0 [1, 2] == [1, 2] pp $ fillList 0 [1, 3] == [1, 0, 3]
readFileStrict :: FilePath -> IO String Source #
KEY: read file strictly
See readFile
SIO.run::NFData sa => SIO sa -> IO sa
SIO.readFile::FilePath -> SIO String
readFileListStrict :: FilePath -> IO [String] Source #
KEY: read file strictly, return a list of string
See readFile
readFileBSList :: FilePath -> IO [ByteString] Source #
readfile to list of ByteString
readFileBS :: FilePath -> IO ByteString Source #
read file and return strict ByteString
readFileSText :: FilePath -> IO Text Source #
read file and return strict Text Text
readFileSTextList :: FilePath -> IO [Text] Source #
read file to list of Text
charToStrictByteString :: Char -> ByteString Source #
Char to strict ByteString
plines :: String -> [String] Source #
KEY: break newlines
Like the lines
function from Prelude, but treat the "\r\n"
and
"\r"
sequences as newlines too, not just "\n"
.
breakNewline :: String -> (String, String) Source #
See plines
replaceByteStringFile :: FilePath -> ByteString -> ByteString -> IO ByteString Source #
KEY: replace pattern inside a file, replace string in a file
- NOTE: It only replace one string in a file, NOT all strings
replaceFileWithBSToNew :: FilePath -> (ByteString, ByteString) -> FilePath -> IO () Source #
KEY: replace pattern inside a file, new file is created. Old file is NOT modified
See readFileRepPat
, searchReplaceAny
, searchReplace
, replaceByteStringFile
replaceFileWithStrToNew :: FilePath -> (String, String) -> FilePath -> IO () Source #
replaceFileWithStr :: String -> String -> FilePath -> IO () Source #
KEY: replace file with string, substitude string with a pattern
- replace all words in a file with pattern string
EXAMPLE: replaceDirWithStr pat sub dir
ISSUE: if sub contains \\
then, only one '\' is written to fname
NOTE: replace word only
file.x replaceMe sub = begin{pmatrix} a & b c & d end{pmatrix} replaceFileWithStr "replaceMe" sub "tmpf.x" cat tmpf.x begin{pmatrix} a & b c & d end{pmatrix}
replaceFileWithWord :: String -> String -> FilePath -> IO () Source #
Search and replace word inside a file, the code is based on matchAllText
in package: Text.Regex.TDFA as TD
See searchReplace
replace word only
let s = "mydog dog-- dog pig cat dog fox" searchReplace s "dog" "[\\0]" "mydog [dog]-- [dog] pig cat [dog] fox"
replaceFileListWord :: [(String, String)] -> FilePath -> IO () Source #
Search replace words with a list of tuple in a file
See searchReplaceListWord
and searchReplace
> searchReplaceListWord [("dog", "cat")] "mydog dog" > "mydog cat"
replaceFileListStr :: [(String, String)] -> FilePath -> IO () Source #
Search replace String with a list of tuple in a file
See searchReplaceListStr
and searchReplaceAny
> searchReplaceListStr [("dog", "cat")] "mydog dog" > "mydog cat"
searchReplaceListWord :: [(String, String)] -> String -> String Source #
Search replace words with a list of tuple
See replaceFileListWord
and searchReplace
and searchReplaceAny
> searchReplaceListWord [("dog", "cat")] "mydog dog" > "mydog cat"
searchReplaceListStr :: [(String, String)] -> String -> String Source #
Search replace words with a list of tuple
See replaceFileListWord
and searchReplace
and searchReplaceAny
> searchReplaceListStr [("dog", "cat")] "mydog dog" > "mydog cat"
replaceDirWithStr :: String -> String -> FilePath -> IO () Source #
KEY: replace pattern with a string in all file in a dir
replaceRegex :: Regex -> String -> String -> String Source #
KEY: replace string, substitute string
Use subRegex
-- Remove all punctuation replaceRegex (mkRegex "[[:punct:]]") "[mya,b,c]" "" ⇒ myabc let r1 = mkRegex "google" let input = "http://google.com" let replacement = "[yahoo]" putStrLn $ subRegex r1 input replacement -- http://[google].com
readFileRepPat :: FilePath -> ByteString -> ByteString -> IO ByteString Source #
KEY: replace pattern inside a file, replace str in file, substitude str in a file
bs <- readFileRepPat "src/searchForm.html" "replaceSearchForm" $ toSBS $ optionHtml autoList
replaceFileWithPat :: FilePath -> ByteString -> ByteString -> IO ByteString Source #
KEY: replace pattern inside a file, replace str in file, substitude str in a file
replaceByteStringFile
readFileRepPat
bs <- replaceFileWithPat "src/searchForm.html" "replaceSearchForm" $ toSBS $ optionHtml autoList
toStrictBS :: ByteString -> ByteString Source #
Convert Lazy ByteString to Strict ByteString
Data.ByteString => Data.ByteString.Lazy
strictBSToString :: ByteString -> String Source #
Convert Strict ByteString to String
strictBSToString = strictTextToStr . strictByteStringToStrictText
toSText :: Typeable a => a -> Text Source #
Convert String, ByteString, Text to Strict Text
let st1 = let s = "a"::String in toSText s -- OK let st2 = toSText ("a"::String) -- OK let st3 = toSText $ "a"::String -- Error
toStr :: Typeable a => a -> String Source #
Convert anthing to String
- Lazy Text to String
- Strict Text to String
- Lazy ByteString to String
- Strict ByteString to String
catMaybe :: Maybe [a] -> Maybe [a] -> Maybe [a] Source #
can be replaced with following:
(++) <$> (Just [1]) <*> (Just [2])
removeSpace :: String -> String Source #
escapeHtml :: String -> String Source #
Escape Html special characters, e.g. only [<
, >
] currently, remove angle bracket
Html special characters can be added
><
, >
, '\', %
escapeAmpersand :: String -> String Source #
escape amperspand &
\( \Rightarrow \) '&'
- See
escapePartial
- See
escapeXML
escapePartial :: String -> String Source #
escape <
, >
, '\'', '"'
- See
escapeAmpersand
- See
escapeXML
escapeXML :: String -> String Source #
escape XML special characters <
, >
, '\'', '"', &
- See
escapeAmpersand
- See
escapePartial
removeIndex :: Int -> [a] -> [a] Source #
Remove element from a list
insertIndexAt
⟹ insert to the next index
removeIndex 1 [1,2,3] [1, 3] removeIndex 3 [] [] removeIndex 1 "abc" "ac"
removeIndex 100 [1, 2] => [1, 2] removeIndex -1 [1, 2] => [1, 2]
removeIndex_new :: Integer -> [a] -> [a] Source #
removeRowCol :: Integer -> Integer -> [[a]] -> [[a]] Source #
Remove specific row and column from a given matrix
removeRowCol 1 2 -- remove the first row and second column
[ M =begin{bmatrix} 1 & 2 & 3 4 & 5 & 6 7 & 8 & 9
end{bmatrix} rightarrow begin{bmatrix} 4 & 6 7 & 9
end{bmatrix} ]
principleSubmatrix :: Int -> [[a]] -> [[a]] Source #
Principle submatrix
Principle submatrix is a square matrix obtained by removing the same set of rows and columns.
principleSubmatrix 1 mat
[ M = begin{bmatrix} a & b & c d & e & f g & h & i end{bmatrix}
rightarrow begin{bmatrix} a & c g & i end{bmatrix}
]
takeX :: Integer -> [a] -> [a] Source #
take
support negative number
if n >= 0 then take n else takeEnd (-n)
dropX :: Integer -> [a] -> [a] Source #
drop
support negative number
if n >= 0 then drop n else dropEnd (-n)
takeWhileX :: (a -> Bool) -> [a] -> [a] Source #
same takeWhile
from GHC.List
takeBS :: Integer -> ByteString -> ByteString Source #
take BS.ByteString
- strict ByteString Data.ByteString
dropBS :: Integer -> ByteString -> ByteString Source #
drop BS.ByteString
- strict ByteString Data.ByteString
splitBS :: Word8 -> ByteString -> [ByteString] Source #
split BS.ByteString
BS.split (c2w_ 'a') "aXaXa" => ["", "X", "X", ""]
trimWS :: String -> String Source #
trim whitespace from the whole string, NOT just head and tail
see trim
head and tail
trimWS s = filter(not . isSpace) s
trimStart :: String -> String Source #
Remove whitespace characters from the start of string.
" dog" => "dog"
trimEnd :: String -> String Source #
Remove whitespace characters from the end of string.
" a b c " => " a b c" "abc" => "abc"
splitListEmptyLine :: [String] -> [[String]] Source #
split list of string when string is empty/space
["dog", " ", "", "cat"] => [["dog"], [], ["cat"]]
splitListHalf :: [String] -> ([String], [String]) Source #
split list into half
- split list into half, ["a", "b", "c"] => (["a", "b"], ["c"])
splitListWhen :: (a -> Bool) -> [a] -> [[a]] Source #
split list 2d with lambda function
Use splitWhen
from Internals
splitListWhen(x -> x == "b") ["a", "b"] => [["a"], []] splitListWhen(x -> x == "b") ["b", "c"] => [[], ["c"]] splitListWhen(x -> x == "b") ["b"] => [[], []] splitListWhen(x -> x == []) [["a"], ["b"], [], ["c"]] [[["a"], ["b"]], [["b"]]]
lengthcurve :: (Double -> Double) -> (Int, Int) -> Double Source #
Calculate the length of a curve for *any* functions
\[ f(x) = x^2 \quad x \in [0, 1] \]
f x = x*x lengthcurve f (0, 1) 1.4689349039867374
[ begin{align*} & text{Divide the curve into } n text{ parts} &x_i in {x_0, x_1, x_2, cdots, x_{n-1}, x_n} &f(x_i) in {f(x_0), f(x_1), f(x_2), cdots, f(x_{n-1}), f(x_n) } &y_i in {x_0^{2}, x_1^{2}, x_2^{2}, cdots, x_{n-1}^{2}, x_n^{2} } s &= sum_{i=1}^{n} sqrt{(x_{i-1} - x_i)^2 + (y_{i-1} - y_i)^2} s_1 &= sqrt{(x_0 - x_1)^2 + (x_0^{2} - x_1^2)^2} s_2 &= sqrt{(x_1 - x_1)^2 + (x_1^{2} - x_2^2)^2} vdots s_{n-1} &= sqrt{(x_{n-2} - x_{n-1})^2 + (x_{n-2}^{2} - x_{n-1}^2)^2} s_n &= sqrt{(x_{n-1} - x_n)^2 + (x_{n-1}^{2} - x_n^2)^2} \ s &= sum_{i=1}^{n} sqrt{(x_{i-1} - x_i)^2 + (y_{i-1} - y_i)^2} s &= sum_{i=1}^{n} sqrt{ Delta x_{i}^2 + Delta y_{i}^2} qquad end{align*}
# 2356 "UsersaaamyfilebitbuckethaskelllibAronModule.hs" ]
- The code is based on length_of_curve
lengthcurveInter :: (Double -> Double) -> (Int, Int) -> Int -> Double Source #
Calculate the length of a curve for *any* functions in a given interval
\[ f(x) = x^2 \quad x \in [0, 1] \]
lengthcurveInter f (0, 1) 200
isBalanced3 :: String -> String -> Bool Source #
KEY: balance bracket, check balanced bracket
[] => True [{}] => True [} => False [{]} => False
isBalanced2 :: String -> String -> (String, Bool) Source #
findBalance :: [(Integer, String)] -> String -> ([(Integer, String)], Bool) Source #
Find all bracket '{, }' until they are balanced
"{{ { <- 1 } <- 2 } <- 3 } <- 4 }" <- 5 return => ([(5,"}")],True)
isBalanced :: String -> Bool Source #
KEY: balance brackets
pp $ isBalanced "" == True pp $ isBalanced "{" == False pp $ isBalanced "}" == False pp $ isBalanced "{}" == True pp $ isBalanced "}{" == False pp $ isBalanced "{}{" == False pp $ isBalanced "}{}" == False
strToLazyText :: String -> Text Source #
String to Lazy Text
lazyTextToStr :: Text -> String Source #
strToStrictText :: String -> Text Source #
KEYS: string to strict text, str to strict text, str to text
String
to Text
strictTextToStr :: Text -> String Source #
Strict Text to String
KEY: strict text to str, text to string
lazyTextToLazyByteString :: Text -> ByteString Source #
lazy Text to lazy ByteString
KEY: lazy Text to lazy ByteString
lazyByteStringToLazyText :: ByteString -> Text Source #
strictTextToStrictByteString :: Text -> ByteString Source #
strict Text to strict ByteString
strictByteStringToStrictText :: ByteString -> Text Source #
Convert Strict ByteString to Strict Text
strictByteStringToLazyByteString :: ByteString -> ByteString Source #
lazyByteStringToStrictByteString :: ByteString -> ByteString Source #
Convert lazy ByteString to strict ByteString
strictTextToLazyText :: Text -> Text Source #
lazyTextToStrictText :: Text -> Text Source #
Lazy Text to Strict Text
strToStrictByteString :: String -> ByteString Source #
String to Strict ByteString, String to ByteString, str to ByteString
strToStrictByteString = strictTextToStrictByteString . strToStrictText
strToLazyByteString :: String -> ByteString Source #
String to lazy ByteString, only for ASCII, not for unicode
str1 = "好" str2 = "good" main = do pp ((LC8.unpack $ LC8.pack str1) == str1) -- False pp ((LC8.unpack $ LC8.pack str2) == str2) -- True
jsonDecode :: FromJSON a => String -> Maybe a Source #
jsonToRecord :: FromJSON a => FilePath -> IO (Maybe a) Source #
KEY: JSON to record, JSON file to record
SEE: UsersaaamyfilebitbucketstackprojectJsonAeson -- JSON file {"editorbeg":100, "editorend":200, "editorfile":"try919591", "editorcmd":"save", "editorcode":"Hello World", "mycat":{"name":"meowmers", "age":1,"list":["dog","cat"] } } -- data EditorCode = EditorCode{ editorbeg::Integer, editorend::Integer, editorfile::String, editorcmd::String, editorcode::String, mycat::Cat } deriving (Show, Generic) instance DA.ToJSON EditorCode where toEncoding = DA.genericToEncoding DA.defaultOptions instance DA.FromJSON EditorCode data Cat = Cat { name :: Text, age :: Int, list :: [String] } deriving (Show, Generic) instance DA.ToJSON Cat where toEncoding = DA.genericToEncoding DA.defaultOptions instance DA.FromJSON Cat meowmers = Cat { name = "meowmers", age = 1, list = ["dog", "cat", "independency Injection"] } editCode = EditorCode { editorbeg = 100, editorend = 200, editorfile = "try919591", editorcmd = "save", editorcode = "Hello World", mycat = meowmers } decodeStr <- jsonToRecord "/tmp/json.json" :: IO (Maybe EditorCode) case decodeStr of Nothing -> Prelude.putStrLn "Not a Valid JSON file" (Just x) -> Prelude.putStrLn $ show x
compileJava :: FilePath -> IO ExitCode Source #
Compile java file
- Given an absoluate path
- return and ExitCode
- The function is used in filewatcher.
docExitCode <- compileJava "/Users/cat/myfile/bitbucket/testfile/compileJavaTest.java" case docExitCode of ExitSuccess -> sys "notify.sh \"gene_javadoc.sh => ExitSuccess\"" ExitFailure x -> sys "notify.sh \"gene_javadoc.sh => ExitFailure\""
pm :: Show a => String -> [[a]] -> IO () Source #
Print matrix with label, print matrix with string,
pm "my matrix" mat ------------------------------------my matrix----------------------------------- [1,2,3] [4,5,6] [7,8,10]
pls :: [String] -> IO () Source #
print list of string without double quotes
- rename: ps => pls (Wed Oct 16 22:18:00 2019)
printMat :: Show a => [[a]] -> IO () Source #
KEY: print matrix, print 2d list
SEE pmat
matrixToStr
let ls = [[1..4] | _ <- [1..4]]
printMat ls
pmat :: Show a => [[a]] -> IO () Source #
KEY: print matrix, print 2d list
SEE printMat
matrixToStr
let ls = [[1..4] | _ <- [1..4]]
pmat ls
matrixToStr :: Show a => [[a]] -> [String] Source #
KEY: matrix to string, 2d list to string, print matrix
SEE printMat
> ls = [[1..4] | x <- [1..4]] > s = matrixToStr ls > mapM_ putStrLn s 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 > wfl "tmpkk.x" s > :!cat tmpkk.x 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4
listSlide :: [a] -> Int -> [[a]] Source #
- KEY: list slide, list sliding, window sliding, sliding window
- @ listSlide [a b c d] 2 > [[a, b], [b, c], [c, d]]
listSlide [a b c d] 5 > []
partList :: Int -> [a] -> [[a]] Source #
Partition list to n chunks
UPDATE: Thursday, 16 November 2023 14:42 PST FIXBUG: partList 0 [1, 2] => in infinite loop
Note: print partList n [] will cause error since print needs concrete type
split list to n blocks
>partList 2 [1, 2, 3, 4, 5] >[[1,2], [3, 4],[5]] >partList 2 [1, 2, 3, 4, 5, 6] >[[1,2], [3, 4],[5, 6]] > partList 0 [1, 2] > [[1, 2]] > partList -1 [1, 2] > [[1, 2]]
partList2_delete :: Int -> [a] -> [[a]] Source #
Partition list to n chunks
Deprecated:
Use: partListDiff
partListDiff :: Int -> Int -> [a] -> [[a]] Source #
Partition list to n chunks
Note: print partList n [] will cause error since print needs concrete type
split list to n blocks @ partListDiff 1 2 [1, 2, 3, 4] ↑ ↑ | + -> block size | + -> distance 1
> [1, 2]
- 2, 3
- 3, 4
- @
splitBlock :: [String] -> String -> [[String]] Source #
KEY: split file with Regex e.g. empty line
NOTE: use better name, splitTable ? @ ls <- readFileToList "tmpx.x" let lss = splitBlock ls "^[[:space:]]*" => split file with whitespace pp lss
let lss = splitBlock ls "^[[:space:]]*(---){1,}[[:space:]]*" => split file "---" let lss = splitBlock ls "^[[:space:]]*(===){1,}[[:space:]]*" => split file "==="
let lss = splitBlock ["a", " ", "b"] "^[[:space:]]*" => [["a"], ["b"]] let lss = splitBlock ["a", "n", "b"] "^[[:space:]]*" => [["a"], ["b"]] let lss = splitBlock ["a", "t", "b"] "^[[:space:]]*" => [["a"], ["b"]]
- - It works in WhiteSpace
let lss = splitBlock ["a", " ", "b"] "^[[:space:]]*" => [["a"], ["b"]] let lss = splitBlock ["a", "n", "b"] "^[[:space:]]*" => [["a"], ["b"]] let lss = splitBlock ["a", "t", "b"] "^[[:space:]]*" => [["a"], ["b"]] @
NOTE: IT DOES NOT WORK if Empty string in the list. See following.
let lss = splitBlock ["a", "", "b"] "^[[:space:]]*" => [["a", "", "b"]]
parseFileBlock :: String -> String -> [String] -> [(Integer, [String])] Source #
KEY: parse file and partition it into blocks according to patterns: bs ws
bs = "^[[:space:]]*(---){1,}[[:space:]]*" -- split with delimiter "---" ws = "[,. ]" -- split with [,. ] parseFileBlock bs ws ["rat", "-----", "my dog eats my cat, my cat eats my dog." ] [(0, ["rat"]), (1, ["my", "dog", "eats", "my", "cat"])]
prefixSuffix :: String -> [String] Source #
lengthK :: Int -> String -> [String] Source #
substring length k
lengthK 2 ["abcd"] ["ab", "bc", "cd"]
substr :: Int -> String -> [[String]] Source #
substring length from 1 to len s
substr 1 "abc" ["a", "b", "c", "ab", "bc", "abc"]
allSubstr :: String -> [[String]] Source #
all substrings length from 1 to len s
allSubstr "abcd" [["a","b","c","d"],["ab","bc","cd"],["abc","bcd"],["abcd"]]
unique :: Ord a => [a] -> [a] Source #
unique, remove duplicate elements from a list
Convert the list to Set
and convert the Set
back to List
unique
does not keep the order of elements
2 3 4 4 5 3 5 => Remove from the right => 2 3 4 5 3 2 3 4 4 5 3 5 => Remove from the left => 2 3 4 3 5
uniqueOrder
keeps the order of elements from left \( \Rightarrow \) right
uniqueOrder :: Ord a => [a] -> [a] Source #
remove duplicated elements and keep the order from left to right
["a", "b", "a", "b"] => ["a", "b"] s = ["a"] s = ["a", "b"] "a"elem
s => ["a", "b"] "b"elem
s => ["a", "b"]
Recur from the right => left instead of (x:cx)
The runtime will be \( \color{red}{\mathcal{O}(n^2)} \)
NOTE: can be better algorithm
mergeListList :: [[String]] -> [[String]] -> [[String]] Source #
mergeListLen :: [a] -> [a] -> Maybe [a] Source #
mergeSortList :: Ord a => [a] -> [a] -> [a] Source #
merge two sorted lists | [1, 4] [3] => [1, 3, 4]
iterateList :: [a] -> (a -> IO ()) -> IO () Source #
codeCapture :: String -> String Source #
binarySearch :: Ord a => a -> [a] -> Bool Source #
Binary Search
qqsort :: (a -> a -> Bool) -> [a] -> [a] Source #
quick sort with lambda function
bad version
qqsort(\x y -> len x < len y) ["tiger", "dog"] => ["dog", "tiger"]
sqVec :: Ord a => Vector a -> Vector a Source #
Quick Sort in Vector, Did not see any speed decreasing
quickSort' :: [Int] -> [Int] Source #
nice version
- TODO rename it
quickSort1 :: Ord a => [a] -> [a] Source #
quickSortAny :: Ord a => [a] -> [a] Source #
Quick Sort for any type, same as quickSort1, just a better name
mergeSortedList :: Ord a => [a] -> [a] -> [a] Source #
merge sorted list
rotateRight :: Integer -> [a] -> [a] Source #
rotate a list to the right
rotateRight 2 [1, 2, 3] [2, 3, 1]
rotateLeft2 :: [[a]] -> [[a]] Source #
rotate a 2d matrix to the left
rotateLeft2 mat
rotateRight2 :: [[a]] -> [[a]] Source #
rotate a 2d matrix to the right
rotateRight2 mat
rotateLeft :: Integer -> [a] -> [a] Source #
rotate a list to the left
rotateLeft 2 [1, 2, 3] [3, 1, 2]
mergeSortC :: (a -> a -> Bool) -> [a] -> [a] Source #
Merge sort for any type
- TODO rename it
mergeSortM :: (Num a, Eq a) => [[a]] -> [[a]] Source #
Merge sort for matrix, special merge sort
[0, 1] [1] => False [0, 1] [1, 1] => True [1, 1] [0, 1] => False [0, 1, 0] [1, 0, 0] => True
groupCount :: [String] -> [(String, Integer)] Source #
groupCount == groupBy . sort
groupCount ["a", "b", "a"] => [("b", 1), ("a", 2)] groupCount == groupBy . sort
- See
groupBy
Create Symbol link for vim under home
.vimrc -> $b/vim/vim.vimrc
- simplify link file in new system
- it might not be very useful
watchDir :: FilePath -> IO Bool Source #
Watch directory
- If any file is modified, then return True
- If a file is added to directory, then return True
- The delay is one second
fileModTime :: FilePath -> IO EpochTime Source #
KEY: file modification time, timestamp, epoch time in second
EpochTime
\( \Rightarrow \) Int64
fileModTimeInt :: FilePath -> IO Int Source #
KEY: file modification time, timestamp, epoch time in second
KEY: epochtime to int
EpochTime
\( \Rightarrow \) Int
EpochTime
\( \Rightarrow \) Int64
fromEnum
Int64
\( \Rightarrow \) Int
fileModTimeInteger :: FilePath -> IO Integer Source #
KEY: file modification time, timestamp, epoch time in second
EpochTime
\( \Rightarrow \) Int64
fromIntegral
Int
\( \Rightarrow \) Integer
intToCTime :: Int -> CTime Source #
KEY: convert int to CTime
Use toEnum
EpochTime
\( \Rightarrow \) Int64
dirModified :: FilePath -> IO [EpochTime] Source #
return a list of timestamps that any files is modified in a directory
EpochTime
\( \Rightarrow \) Int64
fileSizeA :: FilePath -> IO Integer Source #
KEY: Get file size in byte
See hFileSize
openFile
ReadMode
Handle
readSnippet :: FilePath -> IO [([String], [String])] Source #
Read Snippet file $bsnippetssnippet.hs
- See
readSnippetStr
- snippet_test.hs
- Input file: $bsnippetssnippet.hs
main:*.hs: my dog, my cat my fox eats my rat
output: [([head1], [head1_content1]), ([head2], [head2_content2])] [(["main", "*.hs", "my cat", "my dog"], ["main:*.hs: my dog, my cat","my fox eats my rat "])]
$b/snippet/snippet.hs partition blocktexts into list parse the header => latex_eqq:*.tex: latex equation return [(["latex_eqq", "latex equation"]), ["latex_eqq:*.tex: latex equation", "code block"])]
TODO: write readSnippet for Data.ByteString ?
HELP: gx file://Userscatmyfilebitbucketstackprojectjupyterlab/jupyterlab.html
readSnippetStr :: FilePath -> IO [(String, String)] Source #
readSnippetStr without any split
See readSnippet
[("key_name:*.tex: latex", "key_name:*.tex: latex\nline 1\n\line2"])] readSnippetStr::FilePath->IO [(header, codeblock)]
readSnippetToDatabase :: FilePath -> Connection -> IO () Source #
KEY: Read snippet file, insert into database, snippet to database, snippet to db
- read snippet file, insert to database sqlite3
See CodeBlock
data CodeBlock =
CodeBlock
{ id :: Int64
, header :: TS.Text
, codeblock :: TS.Text
} deriving (Eq, Read, Show)
queryDatabaseToFile :: FilePath -> Connection -> IO () Source #
Query Table CodeBlock and write to a file
mapM_ :: Monad m => (a -> m b) -> [a] -> IO()
import Database.SQLite.Simple import Database.SQLite.Simple.FromRow import Database.SQLite.Simple.FromField import Database.SQLite.Simple.ToField import Database.SQLite.Simple.Internal import Database.SQLite.Simple.Ok codeBlocks <- query_ conn "SELECT id, header, codeblock from CodeBlock" :: IO [CodeBlock] let codeList = map (x -> lines . toStr . codeblock $ x) codeBlocks mapM_ (b -> do writeToFileAppend fp b ) codeList
mysqlQuery :: IO () Source #
KEY: Haskell connect to mysql
create user 'user1'@'localhost' identified by 'password'; # mysql => create new user GRANT select, update, delete ON *.* TO 'user1'@'localhost'; # grand permission
GRANT ALL ON *.* to 'user1'@'localhost'; # grand all permissions ALTER USER 'user1'@'localhost' IDENTIFIED WITH mysql_native_password BY 'password' # program can connect to --------------------+ mysql> source /tmp/user.file --------------------+
sudo mysql -u user1 -p # password --------------------- mysql> CREATE DATABASE testdb # create database in mysql mysql> USE testdb # use testdb - database mysql> source mytable.sql # load table, source table, add table
DROP TABLE mytable;
CREATE TABLE mytable(
id INTEGER NOT NULL AUTO_INCREMENT,
name TEXT NOT NULL,
email TEXT NOT NULL,
PRIMARY KEY(id)
);
INSERT INTO mytable(name, email) VALUES("name1", "mailgmail.com");
INSERT INTO mytable(name, email) VALUES("name2", "mail
gmail.com");
INSERT INTO mytable(name, email) VALUES("name3", "mail@gmail.com");
strToStrictByteString
createConfigMap :: [[(String, String)]] -> HashMap String (HashMap String String) Source #
Create a config map for different OS
Use it to replace readConfig
config =[ [("os", "darwin")], [ ("testdb", "myfilebitbuckettestfile/test.db"), ("webappdb", "myfilebitbuckettestfile/haskellwebapp2.db"), ("host", "http://localhost"), ("snippetpath", "myfilebitbucketsnippets/snippet.hs"), ("port", "8000"), ("readSnippetFile", False) ] ]
readFileRemote :: FilePath -> FilePath -> IO () Source #
read file remotely and write to local file
readFileRemote "https://some.com/file.txt" "/tmp/file.xt"
readFileRemoteToList :: FilePath -> IO ByteString Source #
read file remotely and return IO BL.ByteString
bs <- readFileRemoteToList "https://some.com/file.txt"
readFileLatin1 :: FilePath -> IO String Source #
readFile2d :: Read a => FilePath -> IO [[a]] Source #
Read generic type from a file and conver to two dim list, read table
- Seperator is Space
- See
splitSPC
fn = "tmpf.x" tmpf.x 1 2 3 3 4 5 ls <- readFile2d fn :: IO[[Integer]] pre ls fn = "tmpf.x" tmpf.x 0.2 0.3 0.1 0.5 ls <- readFile2d fn :: IO[[Float]] ls ls
FIX: trim string before read it
readFileToInteger2d :: FilePath -> IO [[Integer]] Source #
read two dim matrix from a file, read a list of list Integer from a file
readFile2d
for different type
p1 = "/Users/cat/myfile/bitbucket/testfile/matrix.txt" lss <- readFileToInteger2d p1 pa lss
orgList :: [String] -> [String] Source #
Read dir, all dir or files in [String]
There is error when reading some non utf8 or weird char.
Deprecated, use readFileLatin1ToList
hGetContents: invalid argument (invalid byte sequence) ["f1", "f2"]
Emacs Org mod forms a list
["dog", "cat"] => ["|", "dog", "|", "cat", "|"]
orgTable :: FilePath -> [[String]] -> IO () Source #
Emacs Org mode forms a table
- | cat | dog |
- | cow | pig |
writeToFile :: FilePath -> [String] -> IO () Source #
writeFileBS :: FilePath -> ByteString -> IO () Source #
Write BS.ByteString to file
- writeFileBS used BS.writeFile, nothing else
writeFileBS "file.x" (strToStrictByteString "data")
writeFileListBS :: FilePath -> [ByteString] -> IO () Source #
writeToFileAppend :: FilePath -> [String] -> IO () Source #
writeFileListAppend :: FilePath -> [String] -> IO () Source #
nToFractMat :: (Real a, Fractional b) => [[a]] -> [[b]] Source #
Matrix: Integer to Fractional, convert integer matrix to Fractional matrix
see nToNumMat
class (Num a)=>Fractional a where class (Num a, Ord a)=> Real where class (Real a, Enum a)=> Integral where
nToNumMat :: Num b => [[Integer]] -> [[b]] Source #
Convert an Integer matrix to an Num Matrix
see nToFractMat
writeToFile2dMat :: (Num a, Fractional a, Show a) => FilePath -> [[a]] -> IO () Source #
Write an 2d Matrix to file, write an 2d list to file, write matrix to file
see writeToFileMat
[ begin{bmatrix} 1 & 2 3 & 4 end{bmatrix} Rightarrow
begin{matrix} 1 & 2 3 & 4 end{matrix}
]
m = [[1, 2], [3, 4]] writeToFile2dMat "/tmp/m.x" m :!cat /tmp/m.x
writeToFileMat :: FilePath -> [[String]] -> IO () Source #
write String matrix to file
see writeToFile2dMat
filtermap :: (a -> Maybe b) -> [a] -> [b] Source #
KEY: filter and map simultaneous
filtermap(\x -> elem x ['a', 'e', 'i', 'o', 'u', 'y'] then Nothing else Just (toUpper x)) "abc" remove all the vowels and toUpper => "BC"
Prepend an element to a list if available. Leave the list as it is if the first argument is Nothing. Variant of map which deletes elements if the map function returns Nothing.
https://snipplr.com/view/59474/simultaneous-filter-and--map/
putStrLnBS :: ByteString -> IO () Source #
bs :: [[Double]] -> [Double] -> [Double] -> [Double] Source #
Backward substitute
Given an upper triangle matrix \(A\) and a vector \(\vec{b}\), solve for \(x\)
\[ Ax = b \] [ A = begin{bmatrix} 1 & 2 0 & 4 end{bmatrix}
begin{bmatrix} x_1 x_2
end{bmatrix} = begin{bmatrix} b_1 b_2
end{bmatrix} ]
fs :: [[Double]] -> [Double] -> [Double] -> [Double] Source #
forward substitute
Given a lower triangle matrix \(A\) and a vector \(\vec{b}\), solve for \(x\)
\[ Ax = b \] [ A = begin{bmatrix} 1 & 0 2 & 4 end{bmatrix}
begin{bmatrix} x_1 x_2
end{bmatrix} = begin{bmatrix} b_1 b_2
end{bmatrix} ]
dim :: [[a]] -> (Int, Int) Source #
Find the dimension of a matrix -> (nrow, ncol)
dim [] => (0, 0)
NOTE: there is bug >dim [1]
zipWithArr :: Num a => (a -> a -> a) -> IOArray Int a -> IOArray Int a -> IO (IOArray Int a) Source #
zipWith two mutable array
TODO: change Int to generic type with forall a. ? Problem: when you initialize the array, you need a concrete type such as Int, Float Solution: constrain to (Num a) type
zipWithArrToList :: Num a => (a -> a -> a) -> IOArray Int a -> IOArray Int a -> IO [a] Source #
zipWith two mutable array, and convert to list
TODO: change Int to generic type with forall a. ? Problem: when you initialize the array, you need a concrete type such as Int, Float Solution: constrain to (Num a) type
det :: Num a => [[a]] -> a Source #
Use co-factor expantion to find a determinant of n by n matrix.
- co-factor expantion
- It is very slow.
- Note: \( \det M = \det M^{T} \)
- NOTE: the function should not been used for
Floating
type
multiMatInt :: [[Int]] -> [[Int]] -> [[Int]] Source #
matrix multiplicaiton in Int
multiVec :: Num a => [[a]] -> [a] -> [[a]] Source #
KEY: matrix multiply a column vector
NOTE: return a column-matrix, the vector is in the first column
INPUT: column-matrix RETURN: column-matix
-- treatv
as column vector fw "mat" printMat mat v = [1, 2, 3] fw "v" v m1 = matmultiVec
v fw "m1" printMat m1
multiMatStr :: [[String]] -> [[String]] -> [[String]] Source #
Matrix multiplication in String
m1 = ["a","b"] ["c","d"] m2 = ["x","y"] ["z","w"] > mapM_ print $ multiMatStr m1 m2 ["axbz","aybw"] ["cxdz","cydw"] > mapM_ print m1 ["a","b"] ["c","d"] > mapM_ print m2 ["x","y"] ["z","w"] > pmat mat 1 2 3 4 5 6 7 8 10 > pmat $ tran mat 1 4 7 2 5 8 3 6 10 > pmat $ (map . map) (r -> concatStr r "+") $ (out . zipWith) (a b -> show a ++ "x" ++ show b) mat $ tran mat "1x1+2x4+3x7" "1x2+2x5+3x8" "1x3+2x6+3x10" "4x1+5x4+6x7" "4x2+5x5+6x8" "4x3+5x6+6x10" "7x1+8x4+10x7" "7x2+8x5+10x8" "7x3+8x6+10x10" >
cart :: [[a]] -> [[a]] -> [[([a], [a])]] Source #
cart::[[a]] ->[[a]] -> [[([a], [a])]] cart cx cy = tran $ [[(x, y) | x <- cx] | y <- tran cy]
multiMatDouble :: [[Double]] -> [[Double]] -> [[Double]] Source #
matrix multiplication in Double multiMatDouble::[[Double]]->[[Double]]->[[Double]] multiMatDouble a b = [ [sum $ zipWith (*) ar bc | bc <- (L.transpose b)] | ar <- a]
multiMatR :: [[Rational]] -> [[Rational]] -> [[Rational]] Source #
matrix multiplication in Rational Number
> pmat matr 1 % 1 2 % 1 3 % 1 4 % 1 5 % 1 6 % 1 7 % 1 8 % 1 10 % 1 > pmat $ multiMatR matr matr 30 % 1 36 % 1 45 % 1 66 % 1 81 % 1 102 % 1 109 % 1 134 % 1 169 % 1
multiMatNum :: Num a => [[a]] -> [[a]] -> [[a]] Source #
multiMat :: Num a => [[a]] -> [[a]] -> [[a]] Source #
KEY: Use outer product to compute matrix multiplication.
[ begin{bmatrix} 1 & 2 & 3 4 & 5 & 6 7 & 8 & 9
end{bmatrix} ]
- use outer product to compute matrix mulitplication
- outer(col_1 row_1) + outer(col_2 row_2) + outer(col_3 row_3)
- matrix multiply vector
-- column vector [[1], [2], [3]] -- row vector [[1, 2, 3]] -- matrix * vector -- matrix m m = [ [1, 2, 3], [4, 5, 6], [7, 8, 9] ] -- vector V [a, b, c] to matrix form v = [ [a, 0, 0], [b, 0, 0], [c, 0, 0] ] matrix multiply vector m * v
[ begin{bmatrix} 1 & 2 & 3 4 & 5 & 6 7 & 8 & 9 end{bmatrix}
times begin{bmatrix} 1 2 3 end{bmatrix} Can be written as following
begin{bmatrix} 1 & 2 & 3 4 & 5 & 6 7 & 8 & 9 end{bmatrix}
times begin{bmatrix} 1 & 0 & 0 2 & 0 & 0 3 & 0 & 0 end{bmatrix}
]
multiRatMat :: [[String]] -> [[String]] -> [[String]] Source #
matrix multiplication in String/Rational
sumRatList :: [String] -> String Source #
matId :: Num a => Int -> [[a]] Source #
KEY: identity matrix
matId 3 out (a b -> a == b ? 1 $ 0) [1..3] [1..3]
reduceForm :: [[String]] -> [[String]] Source #
reduceForm
list of rational
stringToFloat :: String -> Float Source #
stringToListInt :: String -> [Int] Source #
Convert string to a list of Int
stringToListInt "[1, 2]" [1, 2] stringToListInt "[1..3]" error
isWord :: String -> Bool Source #
Check a string whether it is a word or not
Word is defined as "^[[:alpha:]]+$" isWord "dog" True isWord "dog1" False isWord::String -> Bool isWord s = matchTest (mkRegex "^[[:alpha:]]+$") s
isInWord :: Char -> Bool Source #
Check a string whether it is a word or not
Word should be defined as [a-zA-Z0-9_] according to vim doc :h pattern
hasWordChar :: String -> Bool Source #
Check whether String contain Word char
Word = [a-zA-Z0-9_] hasWordChar "abc_efg" -- True hasWordChar "abc-" -- False
perm :: [a] -> [[[a]]] Source #
Permutation of any type, the algo is based on prefix string
fun (prefix, int index, removeIndex(index str))
perm "12" [["12", "21"]]
TODO: fix, the code has error.
perm2 :: Eq a => [a] -> [[a]] Source #
Permutation of any type
The code is based on prefix string algorithm
perm "12" [["12", "21"]]
abc a p(bc) b p(c) c p() c p(b) b p() b p(ac) a p(c) c p() c p(a) a p() c p(ab) a p(b) b p() b p(a) a p()
abc a bc b c [[]] c b [[]] b ac a c [[]] c a [[]] c ab a b [[]] b a [[]]
rangeNum :: Eq a => Integer -> [a] -> [[a]] Source #
KEY: facebook interview question
- find all the list that in increasing order, and the length is n
rangeNum 3 [1, 2, 3, 4] [1, 2, 3], [2, 3, 4], [1, 2, 4]
perm3 :: [a] -> [[a]] Source #
And other Permutation
- 1, 2, 3
x : xs 1 [2,3] x : xs 2 [3] x : xs 3 []
perm([1, 2, 3]) 1 : perm([2, 3]) 2 : perm([3]) 3: perm([])
- 1 2 3
- [2 3 1] [3 1 2] x : cx x:cx x : cx 1:[2,3] 2:[3,1] 3:[1,2] 1:[3,2] 2:[1,3] 3:[2,1]
normList :: Floating a => [[a]] -> [[a]] Source #
Normalize a list as vector
[[1, 2, 3]] is row vector [[1], [2], [3]] is column vector
\[ \| \vec{v} \| = \sqrt{x^2 + y^2 + z^2} \quad \text{ where } \vec{v} = \begin{bmatrix} x & y & z \end{bmatrix} \]
projn :: Fractional a => [[a]] -> [[a]] -> [[a]] Source #
projection from u onto v in n dimensional list | | puv = (u v /v) v | |
rMatrixUpperTri :: Num c => [[[c]]] -> [[[c]]] -> [[c]] Source #
Form a almost R matrix: almost an upper triangle matrix
QR_Decomposition [ R' = begin{bmatrix} leftv_1 right & leftv_2 right & leftv_3 right emptyset & leftv_2 right & leftv_3 right emptyset & emptyset & leftv_3 right
end{bmatrix} quad R = begin{bmatrix} leftv_1 right & leftv_2 right & leftv_3 right 0 & leftv_2 right & leftv_3 right 0 & 0 & leftv_3 right
end{bmatrix} R' neq R
]
rejection :: Fractional a => [[[a]]] -> [[[a]]] -> [[[a]]] Source #
rejection \(v_k\) onto span of \( \{ a_1 \dots a_{k-1} \} \)
QR_Decomposition \[ a_k = v_k - \sum_{i=1}^{k-1} \frac{\left<v_k, a_i \right>}{\left<a_i, a_i \right> } a_i \]
- v3 projects onto \( \{a_1, a_2 \} \)
a3 = v3 - ((projn v3 a1) + (projn v3 a2))
- if the matrix is singular then one of \( \left\| a_k \right\| = 0 \)
- that can be used to determinate the determinant of a matrix, but not the sign of a determinant
- compute the determiant is hard problem: \( \mathcal{O}(n^3) \), there is better algo.
qrDecompose' :: [[Double]] -> ([[Double]], [[Double]]) Source #
QR decomposition or QR factorization
- Given \(M\) is square matrix, there exists a pair of matrices \( Q \) is unitary matrix and \( R \) is upper triangle matrix such that: \[ M = QR \]
addRL :: [String] -> [String] -> [String] Source #
Addition for two list of Rational strings
addRL ["1/2", "1/2"] ["1/2", "1/2"] ["1/1", "1/1"]
eightQueen :: [[Integer]] -> [(Integer, Integer)] -> Integer -> Integer -> [[Integer]] Source #
The algorithm uses backtrack.
- Move top left corner to right and down
- IF the move is valid THEN set (c, r) = 1, AND move one level down to (c+1, 0)
- IF the move is not valid THEN move to (c, r+1)
- Move (c,r) from left to right
- IF (c,r) is valid move
- THEN go down one level deep, => (c+1,0)
- ELSE goto (c, r+1)
- IF (c, r) is the right most position, AND IF (c,r) is valid move
- THEN go down to (c+1, 0)
- ELSE backtrack => take the previous valid move and reset (c,r)=0 AND check whether (c, r+1) is valid move.
- IF (c, 0) is the bottom level,
- THEN we are done!
let m1 = geneMat 10 Zero pa $ eightQueen m1 [] 0 0
rep2d :: (Integral n1, Integral n2) => [[a]] -> n1 -> n2 -> a -> [[a]] Source #
Replace element in position (c, r) with element n in 2d matrix. replace element, replace matrix, replace 2d array
replace1d :: Int -> (a -> a) -> [a] -> [a] Source #
Replace index p element with a function f
replace1d 1 (const 2) [0, 0, 0] -- [0, 2, 0]
replace2d :: a -> (Int, Int) -> [[a]] -> [[a]] Source #
Replace index (c, r) element with a value v
replace2d 1 (const 2) [0, 0, 0] -- [0, 2, 0] replace2d 5 (2, 1) [[1, 1, 1], [1, 1, 1], [1, 1, 1]] [[1,1,1],[1,1,1],[1,5,1]]
leftDiagonal :: [[Integer]] -> Integer -> Integer -> [Integer] Source #
Collect all the elements from left diagonal of a matrix.
mat = [ [1, 2, 3], [4, 5, 6], [7, 8, 10] ] leftDiagonal mat 0 0 [7, 5, 3]
rightDiagonal :: [[Integer]] -> Integer -> Integer -> [Integer] Source #
Collect all the elements from right diagonal of a matrix.
mat = [ [1, 2, 3], [4, 5, 6], [7, 8, 10] ] rightDiagonal mat 0 0 [10, 5, 1]
reverseWord :: String -> String Source #
reverse words in string
tran :: [[a]] -> [[a]] Source #
Transpose matrix
[ begin{bmatrix} a & b c & d end{bmatrix} Rightarrow
begin{bmatrix} a & c b & d end{bmatrix}
]
- NOTE: > map tail [[1], [2]] => [[], []]
-- Fri 14 Oct 23:32:14 2022 -- The code DOES NOT work if the matrix: m = [[1, 2], [3]] tran::[[a]]->[[a]] tran [] = [] tran ([]:_) = [] tran x = (map head x):tran(map tail x) [1, 2, 3] : x0 = [1, 2, 3] => [2, 3] => [3] => [] => [] x1 = [4, 5, 6] => [5, 6] => [6] => [] => [] x2 = [7, 8, 9] => [8, 9] => [9] => [] => [] 1 : <- 4 : <- 7 : [] 2 : <- 5 : <- 8 : [] 3 : <- 6 : <- 9 : [] (9 ) <- (8) <- (7) (6) <- (5) <- (4) (3) <- (2) <- (1)
sortRow :: [[Integer]] -> [[Integer]] Source #
concat operator | pp $ "n=" +: fun x | (+:)::(Show a)=> String-> a -> String | (+:) s a = s ++ (show a)
sort row for list of list
upperTri :: [[Integer]] -> [[Integer]] Source #
Tranform the matrix to echolon/upper triangle form
KEY: upper triangle, matrix to upper triangle
- Thu Jan 10 23:29:20 2019
- gx Matrix to Upper Triangle
- gf Userscatmyfilebitbucketmathupper_triangle.tex
- Note: the determinant is different than the original matrix
- Thu Jan 10 23:29:27 2019
- Add lcm to the multiplier, make matrix dim from 6 to 13
- TODO: fix the num overflow issue
- Wednesday, 15 May 2024 11:45 PDT
- Update: Use
mergeSortC
with compare function
divI :: Fractional a => Integer -> Integer -> a Source #
Division is painful
class (Num a)=> Fractional a where (/):: a -> a -> a divI::(Fractional a)=>Integer -> Integer -> a class Num a where fromInteger::Integer -> a class (Num a, Ord a)=> Real a where fromIntegral::(Integral a, Num b) => a -> b fromIntegral = fromInteger . toInteger class (Real a, Enum)=> Integral a where [1] toInteger(Real a, Enum a)=> a -> Integer [2] fromInteger::(Num a)=>Integer -> a [3] proof: [1] [2] [3] => fromIntegral(Num a) => Integral -> a
inverse :: [[Double]] -> ([[Double]], [[String]]) Source #
Find the invertible matrix, return ([[]], [[]]) if the matrix is singular
- The code does not check whether the matrix is singular or not
m <- randomMatrix 7 7 -- Int matrix m' = (map . map) rf m -- Double matrix inverse m' inverse::(Integral a, Fractional a, Real a, Show a, Eq a)=>[[a]]->([[a]], [[String]]) inverse::(Fractional a, Show a, Eq a)=>[[a]]->([[a]], [[String]])
- TODO: Remove division
isInver :: (Fractional a, Ord a) => [[a]] -> Bool Source #
check whether a matrix is singular using QR_Decompoisition
isInvertible :: [[Integer]] -> Bool Source #
Multiply all the diagonal elements and check whether the product is zero or not
Algorithm:
- Find the upper triangle of m
- Multiply all the diagonal entries
- If their product is NOT zero then it is invertible, otherwise singular
-- Test case: rm <- randomMatrix 100 100 pp $ isInvertible rm
mlist :: Integer -> [Integer] -> [Integer] Source #
Integer multiply integer list
reverse $ 9 x [9, 8] = [8, 8, 2]
randomTemp :: IO String Source #
KEY: random temp file name, random tmp file
randomTemp::IO String -- randomTemp => tmp223423423.txt
drawInteger :: Integer -> Integer -> IO Int Source #
KEY: random Integer
- generate Integer from x to y random number
randomInteger :: Integer -> Integer -> IO Integer Source #
KEY: random Integer
- alias of
drawInteger
randomDouble :: Int -> IO [Double] Source #
randomFloat :: Int -> IO [Float] Source #
randomFrac :: Fractional a => Int -> IO [a] Source #
Generate list of Fractional in \( x \in [0 \dots n], n = 100 \)
[0.3, 0.4, 0]
Num and Fractional are type class so you can NOT do [Num] or [Fractional]
Type class in Haskell is similar like interface in Java, but there are many differences
e.g. Integer implement Num => Integer is a concrete class e.g. Fractional inherits from Num => Fractional type class e.g. Float implement Fractional => Float is concrete class
randomList :: Integer -> IO [Integer] Source #
generate random of list Integer
randIntList :: Int -> (Int, Int) -> IO [Int] Source #
List of random Int
NOTE: Use randomIntegerList
randomIntList::Integer ->(Integer, Integer) -> IO [Integer] randomIntList 0 _ = return [] randomIntList n (s, e)= do r <- randomRIO (s, e) rs <- randomIntList (n - 1) (s, e) return (r:rs)
randomIntList :: Int -> (Int, Int) -> IO [Int] Source #
list of random Int
Same as randIntList
SEE: randomIntegerList
randomIntegerList :: Integer -> (Integer, Integer) -> IO [Integer] Source #
randomMatrix :: Num a => Int -> Int -> IO [[a]] Source #
Generate \( m \times n \) random matrix.
geneRandMat :: Num a => (Int, Int) -> IO [[a]] Source #
Generate \( m \times n \) random matrix.
Same as randomMatrix
geneMat1ToN :: Num a => Integer -> [[a]] Source #
Generate a matrix from 1 to \( n \times n \) with dimention n
geneMat1ToN 2 [[1, 2], [3, 4]]
geneMatMN :: Integer -> Integer -> [[Integer]] Source #
Generate a matrix from 1 to \( m \times n \)
geneMat1ToN 2 3 [[1, 2, 3], [4, 5, 6]]
compileHaskellToBin :: String -> String -> IO () Source #
Compile haskell code to $ffmybinmyHaskell => create symbol link $sym/sym | [file:myHaskell.hs] [sym:symbol] link name in $sym
strCompareIC :: String -> String -> Bool Source #
compare two string ignore cases
baseName :: FilePath -> String Source #
file base name
KEY: file extension, extension, basename, base name, file ext
baseName "/dog/file.txt" => "file" takeFileName gives "file.ext" takeDirectory gives "/directory" takeExtension gives ".ext" dropExtension gives "/directory/file" takeBaseName gives "file" "/directory" </> "file.ext". "/directory/file" <.> "ext". "/directory/file.txt" -<.> "ext".
takeFileNameT :: Text -> Text Source #
gotoCurrDir :: IO () Source #
Goto current directory, use in script
dirWalk :: FilePath -> (FilePath -> IO [String]) -> IO [String] Source #
KEY: Walking directory with filter or lambda function: upper case file extension
- if there is file, then append it to list
- otherwise, walking inside the dir
- Pass lambda func: (FilePath -> IO [String]) as argument
-- ls all files recursively let f fn = return [fn] in dirWalk f "/tmp" let f fname = takeExtension fname == ".png" then return [fname] else return [] ls <- dirWalk f "/tmp" ls dirWalk (x - x == ".png") "/tmp"
dirWalkPathList :: (FilePath -> IO [String]) -> [FilePath] -> IO [String] Source #
KEY: walk through a list of dir
p1 <- getEnv "m" p2 getEnv "www">= x -> return $ x / "pdf" dirWalkPathList (p -> let ex = takeExt p in ex == ".tex" ? return [x] $ return []) [p1, p2]
getDirContent :: FilePath -> IO [FilePath] Source #
get directory contents
lsRegex :: String -> RegexStr -> IO [String] Source #
KEY: list file with regex match, see lsRegexFull
, list file with filter, file filter
ff <- lsRegex (getEnv j) "\\.java$" -- list all java file ff <- lsRegex (getEnv j) "^try" -- list all file names starts with "try"
isDir :: FilePath -> IO Bool Source #
check whether a given file is a directory or symbol link to a directory
isDir p = doesDirectoryExist p
Also see isFile
fileExistA :: FilePath -> IO Bool Source #
doesExistF :: FilePath -> IO Bool Source #
setCurrentDir :: FilePath -> IO () Source #
set current directory
asplitPath :: FilePath -> [String] Source #
split path
asplitPath "/dot/cat/" ["dog", "cat"] asplitPath "dot/cat/" ["dog", "cat"] asplitPath "/dot/cat" ["dog", "cat"] asplitPath "dot/cat" ["dog", "cat"]
splitPathA :: FilePath -> [FilePath] Source #
splitPathA from System.FilePath.Posix.splitPath
splitPathA "/dog/cat/" ["/", "dog/", "cat/"] splitPathA "/dog/cat" ["/", "dog/", "cat"] splitPathA "dog/cat" ["dog/", "cat"] splitPathA "/" ["/"] splitPathA "./" ["./"]
takeIf :: (a -> Bool) -> [a] -> [a] Source #
take all the elements if \( f(x) \) condition is true
- It is same as
takeWhile
takeIf (\x -> head x == '-') ["-a", "-b", "cc"] ["cc"]
dropIf :: (a -> Bool) -> [a] -> [a] Source #
drop all the elements if \( f(x) \) condition is true
- It is same as
dropWhile
dropIf (\x -> head x == '-') ["-a", "-b", "cc"] ["-a", "-b"] dropIf (\x -> x == ' ') " abc" "abc"
dropPathEnd :: Integer -> String -> String Source #
takePathEnd :: Integer -> String -> String Source #
copyRename :: FilePath -> String -> IO () Source #
- copy FilePath to "/tmp" | 2. move the file back to dir with newName | copy file and rename it in the same dir
copyFileToDir :: FilePath -> FilePath -> IO () Source #
If source is valid file and dest is valid dir, otherwise error
createFile :: FilePath -> IO () Source #
create empty file
listDirFilter :: FilePath -> String -> IO [FilePath] Source #
List file with a Regex filter
SEE: Same as lsFileFilter
e.g. all html files
>ls <- listDirFilter pa "\.html$"
lsFileFilter :: FilePath -> String -> IO [FilePath] Source #
List file with a Regex filter
SEE: Same as listDirFilter
e.g. all html files
>ls <- lsFileFilter pa "\.html$"
renameAllFile :: String -> String -> IO () Source #
rename all files in path, e.g. s=XXX img.JPG => img_XXX.JPG
setCursorPos :: Int -> Int -> IO () Source #
setCursorPosStr :: Int -> Int -> String Source #
getTerminalSize :: IO (Int, Int) Source #
KEY: get terminal size, get screen size, get console size
- See
getScreenSize
- See
ANSI
getScreenSize :: IO (Int, Int) Source #
KEY: get screen size, get console size
- See
getTerminalSize
- See
ANSI
sys :: String -> IO ExitCode Source #
Do not need to return IO [String] like run
If command error, process will not be terminated unless following error:
- PermissionDenied
- ResourceExhausted
- UnsupportedOperation
More detail system
- following will not work if use
run
mapM (\x -> run "git lone " ++ x) listdir
- change to
mapM (\x -> system "git clone " ++ x) listdir
system::String -> IO ExitCode sys s = system s
Use inside GHCi or use :! cmd in GHCi
ExitCode
See ExitCode document
- Defines the exit codes that a program can return.
data ExitCode = ExitSuccess -- ^ indicates successful termination; | ExitFailure Int -- ^ indicates program failure with an exit code. -- The exact interpretation of the code is -- operating-system dependent. In particular, some values -- may be prohibited (e.g. 0 on a POSIX-compliant system). deriving (Eq, Ord, Read, Show, Generic)
linesBS :: ByteString -> [ByteString] Source #
Check type of list of String
Check type of list of ByteString
Check type of String
linesSText :: Text -> [Text] Source #
KEY: lines for strict Text
Deprecated
USE: linesST
isDigitStr :: String -> Bool Source #
Does string contain digit only.
- See
isDigit
isLetterStr :: String -> Bool Source #
Does string contain letter only.
- See
isLetter
isLetterChar
isLetterChar :: Char -> Bool Source #
isDigitChar :: Char -> Bool Source #
run' :: String -> IO () Source #
run shell cmd, send output to std_out
- run' does not wait for the process to finish
run :: String -> IO [String] Source #
Run shell cmd, capture std_out
- some issue with waitForProcess
- it might be deadlock, e.g. run "ps aux"
- man ps -x => still d't underand why the process is not terminated
- top command issue => process is not terminated
- 1. Change it to System, there is issue with the function
- TODO: fix it:o
- There is still some issues, use
system
instead, Tue Jan 28 11:46:22 2020
runShell :: String -> IO (ExitCode, Text, Text) Source #
Run shell command with Turtle lib, shell command (ExitCode, stdoutx, stderr)
(e2, so, si2) <- runShellcmd if e2 /= ExitSuccess then let rcode = ReplyCode{rcmd="", rerror = si2, stdoutx=si2} replyJson = toSBS $ DA.encode $ rcode in response $ responseNothingBS replyJson else do pp so let replyCode = ReplyCode{rcmd="", rerror="", stdoutx= so} let replyJson = toSBS $ DA.encode $ replyCode response $ responseNothingBS replyJson
runShell
is same as runSh
, cmd is String
shellStrictWithErr :: MonadIO io => Text -- ^ Command line -> Shell ByteString -- ^ Chunks of bytes written to process input -> io (ExitCode, ByteString, ByteString) -- ^ (Exit code, stdoutx, stderr) shellStrictWithErr cmdline = systemStrictWithErr (Process.shell (Data.Text.unpack cmdline))
df :: Fractional a => (a -> a) -> a -> a Source #
Differentiate on \(f(x)\)
Find the first derivative at \( x \) on function \( (a \rightarrow a)) \)
x = 1.0 df (\x ->x^2) x 2.0
\( f(x) = x^2 \Rightarrow f'(x) = 2x \Rightarrow f'(1.0) = 2.0 \)
First derivative on f or slop of f at point x
\( f'(x) = \lim_{h \rightarrow 0} \frac{f(x + h) - f(x)}{h} \)
tangent :: Fractional a => (a -> a) -> a -> a -> a Source #
Compute the tangent equation at point \((x_0, f(x_0))\) for function \( f \)
Find a tangent equation at \( x_0 = 1.0 \) in \( f(x) = x^2 \)
tanglent (\x -> x^2) 0 1
Tangent equation:
\( f'(x) = \frac{y - y_0}{x - x_0} \)
\( y = f'(x_0)(x - x_0) + y_0 \)
e.g.
\( f(x) = x^2 \)
\( \Rightarrow f'(x_0) = 2x_0 \)
\( f (x) = x^2 \) where \( x = x_0 \)
\( y = 2x_0(x - x_0) + y_0 \) where \( y_0 = f (x_0) \)
\( f' (x_0) = \frac{y - y_0}{x - x0} \)
\( y = f'(x_0)(x - x_0) + y_0 \)
tangentVec :: Fractional a => (a -> a) -> a -> a -> (a, a) Source #
Compute the tangent vector at point (x0, f x0)
oneRoot :: (Double -> Double) -> Double -> Double -> Double -> Maybe Double Source #
Find root for any polynomial function
- Example: FindRoot
- Partition the interval [x0, xn] into list = [x0, x1) [x1, x2) [x2, x3) ..[x(n-1), xn)
- Concat [xn, xn] with the list since the left boundary is checked only
- Note: f(xn) might be zero, we need to check the xn boundary
- TODO: need to check f(xn), DONE, concat [xn, xn] to the list
Good test cases:
\( f(x) = x^2 - 4 \quad x \in [-2, 2] \)
\( f(x) = x^5 -4x^4 + 0.1x^3 + 4x^2 - 0.5 \quad x \in [-4, 4] \Rightarrow \) 5 solutions
- limitation:
- if each subinterval contains two or more values, then ONLY one value can be found
- subinterval can be adjusted in arbitrary small
[0, 2] (2-0)/2 = [0, 1, 2] = [0, 1) ∪ [1, 2) ∪ [2, 2]
rootList :: (Double -> Double) -> Double -> Double -> Double -> Integer -> [Maybe Double] Source #
Find all the roots for a given close interval: [1, 2], 1 or 2 might be the root |
out :: (a -> b -> c) -> [a] -> [b] -> [[c]] Source #
generic outer product or sth, inspired by APL
Update: Switch row and column to similar to 2d array or APL outer product
out (x y -> x == y ? 1 $ 0) [1, 2, 3] [1 2] | 1 | 2 | -----------+ 1 | x | 0 | -----------+ 2 | 0 | x | -----------+ 3 | 0 | 0 | -----------+ -- identity matrix > m = out (a b -> a == b ? 1 $ 0) [1..4] [1..4] > pmat m 1 0 0 0 0 1 0 0 0 0 1 0 0 0 0 1
outerStr :: (a -> a -> a) -> [[a]] -> [[a]] -> [[a]] Source #
KEY: outer product for string
DATE: Wednesday, 28 February 2024 12:10 PST
> v0 = [ ["x"], ["y"] ] > h0 = [["x", "y"]] > > printMat $ outerStr (a b -> a ++ b) v0 h0 > "xx" "xy" > "yx" "yy"
zipWith2 :: Num a => (a -> a -> a) -> [[a]] -> [[a]] -> [[a]] Source #
zipWith in two dimensions, zipWith matrix
zipWith2(Num a) => (a -> a -> a) ->[[a]] ->[[a]] -> [[a]] zipWith2 f a b = [ zipWith f ra rb | (ra, rb) <- zip a b] zipWith2::(Num a)=>(a ->a ->a)->[[a]]->[[a]]->[[a]] zipWith2 f m1 m2 = zipWith(x y -> zipWith(x1 y1 -> f x1 y1) x y) m1 m2
insertTries :: String -> XNode -> XNode Source #
insert operation for Tries data structure
let xn = insertTries "a" (XNode M.empty False) let xxn = insertTries"ab" xn pp $ "containsTries=" <<< (containsTries "a" xxn == True) pp $ "containsTries=" <<< (containsTries "ab" xxn == True)
- If String is empty return XNode is the end of a word
- If x points to Nothing(x is not on the Tries), then recur to cx
- If x points to an XNode, then recur to cx
insertTriesList :: [String] -> XNode -> XNode Source #
Insert list of strings to Tries, see insertTries
containsTries :: String -> XNode -> Bool Source #
contain operation for Tries data structure
let xn = insertTries "a" (XNode M.empty False) let xxn = insertTries"ab" xn pp $ "containsTries=" <<< (containsTries "a" xxn == True) pp $ "containsTries=" <<< (containsTries "ab" xxn == True)
Most functions are related to Binary Search Tree
- Thu Nov 8 21:24:37 2018
insertNode :: Ord a => Tree a -> a -> Tree a Source #
Instances
Foldable LeafyTree Source # | foldMap combine foldable monoid type to a monoidclass Foldable t where foldMap ::(Monoid m) => (a -> m) -> t m -> m a -> m, a function converts any type to monoid type -- what is the identity? class Semigroup a => Monoid a where mempty :: a mconcat :: [a] -> a main = do let tree1 = Leaf "a" let s = foldMap id tree1 pp s let tree2 = Branch [Leaf "a"] pp $ foldMap id tree2 let tree3 = Branch [Leaf "a", Leaf "b", Branch [Leaf "a2", Leaf "b2"]] pp $ foldMap id tree3 pp $ foldMap (Sum . length) tree3 |
Defined in AronModule fold :: Monoid m => LeafyTree m -> m foldMap :: Monoid m => (a -> m) -> LeafyTree a -> m foldMap' :: Monoid m => (a -> m) -> LeafyTree a -> m foldr :: (a -> b -> b) -> b -> LeafyTree a -> b foldr' :: (a -> b -> b) -> b -> LeafyTree a -> b foldl :: (b -> a -> b) -> b -> LeafyTree a -> b foldl' :: (b -> a -> b) -> b -> LeafyTree a -> b foldr1 :: (a -> a -> a) -> LeafyTree a -> a foldl1 :: (a -> a -> a) -> LeafyTree a -> a elem :: Eq a => a -> LeafyTree a -> Bool maximum :: Ord a => LeafyTree a -> a minimum :: Ord a => LeafyTree a -> a |
isBST :: Ord a => Tree a -> Bool Source #
check whether a Tree is Binary tree
defintion of BST
- Null is BST
- Left subtree is BST
- Right subtree is BST
- minimum of left subtree is less than parent node
- maximum of right subtree is greater than parent node
lca :: Eq a => Tree a -> a -> a -> Maybe a Source #
Lease common ancestor
- assume two nodes are in the tree
- if two nodes are in the same path then the top node will be LCA
buildTree :: [Char] -> [Char] -> Tree Char Source #
Build binary tree from preorder and inorder
- Get the root from preorder , the first element is the header
- Get the leftsubtree and rightsubtree from inorder with the root from previous step
- Partition the preorder and inorder with previous two steps
- Use smaller preorder and inorder on the left subtree and right subtree to do recursion calls
2 1 3 => 1 2 3 inorder 2 1 3 => 2 1 3 preorder
anagram :: String -> [String] -> [String] Source #
Find all anagrams from a list of strings
anagram "dog" ["god", "cat", "ogd"] ["god", "ogd"]
redisExtractAronModule :: String -> [String] -> [([String], Integer, [String])] Source #
Extract AronModule.hs functions out
gx file://Userscatmyfilebitbucketstackprojectjupyterlab/readAronModule.html
[( [ "AronModule.f" , "AronModule.fu" , "AronModule.fun" , "AronModule.funx" , "AronModule.n" , "AronModule.nx" , "AronModule.u" , "AronModule.un" , "AronModule.unx" , "AronModule.x" ] , 30003 , [ "funx::(Integral a, Num b) => a -> b" ] )]
redisExtractJavaMethod :: String -> [String] -> [([String], Integer, [String])] Source #
KEY: Parse Java method name, extract method name and form a list [([String], Integer, [String])]
File format: jname = "UserscatmyfilebitbucketjavalibAron.java"
The list can be used in Redis Server
["line1", "line2"] -> [([k0, k1], 1, ["line1"])]
["line1", "line2"] -> [([k0, k1], 1, ["line1"])] Logger logInit(String className, String fName){} ( [ Aron.I , Aron.In , Aron.Ini , Aron.Init , "Aron.g" , "Aron.gI" , "Aron.gIn" , "Aron.gIni" , "Aron.gInit" , "Aron.i" , "Aron.it" , "Aron.l" , "Aron.lo" , "Aron.log" , "Aron.logI" , "Aron.logIn" , "Aron.logIni" , "Aron.logInit" , "Aron.n" , "Aron.ni" , "Aron.nit" , "Aron.o" , "Aron.og" , "Aron.ogI" , "Aron.ogIn" , "Aron.ogIni" , "Aron.ogInit" , "Aron.t" ] , 10002 , [ "Logger logInit(String className, String fName){" ] )
redisExtractJavaMethodWithPackage :: String -> [String] -> [([String], Integer, [String])] Source #
KEY: Parse Java method name, extract method name and form a list [([String], Integer, [String])]
File format: jname = "UserscatmyfilebitbucketjavalibAron.java"
The list can be used in Redis Server
["line1", "line2"] -> [([k0, k1], 1, ["line1"])]
redisExtractSnippet :: [([String], [String])] -> [([String], Integer, [String])] Source #
KEY: extract code block from Userscatmyfilebitbucketsnippetssnippet.hs
gx file://Userscatmyfilebitbucketstackprojectjupyterlab/redisSnippet.html
cab c -> cab dog ca -> cab dog cab -> cab dog c -> 100 ca -> 100 cab -> 100 100 -> cab dog
textArea :: Integer -> Integer -> String -> String Source #
Html textarea textArea row col string textArea 4 5 "dog"
htmlTableRowCol :: Int -> Int -> [String] Source #
Generate r row and c col table
htmlTableRowColSText :: Integer -> Integer -> [Text] Source #
Generate r row and c col table
Find the name of OS from environment_variable OSTYPE
- Some OS might not set the environment variable name: OSTYPE
- OSTYPE might be set manually in file such as .profile
- Currently it supports MacOS and FreeBSD
- MacOS = "darwin"
- FreeBSD = "freebsd"
data ShellHistory Source #
Project HOMEmyfilebitbucketstackprojectInsectHistoryToSqlite3
Instances
Eq ShellHistory Source # | |
Defined in AronModule (==) :: ShellHistory -> ShellHistory -> Bool (/=) :: ShellHistory -> ShellHistory -> Bool | |
Read ShellHistory Source # | |
Defined in AronModule readsPrec :: Int -> ReadS ShellHistory readList :: ReadS [ShellHistory] readPrec :: ReadPrec ShellHistory readListPrec :: ReadPrec [ShellHistory] | |
Show ShellHistory Source # | |
Defined in AronModule showsPrec :: Int -> ShellHistory -> ShowS show :: ShellHistory -> String showList :: [ShellHistory] -> ShowS | |
FromRow ShellHistory Source # | import Database.SQLite.Simple.FromRow | two fields: shId, shcmd |
Defined in AronModule fromRow :: RowParser ShellHistory | |
ToRow ShellHistory Source # | import Database.SQLite.Simple.ToRow |
Defined in AronModule toRow :: ShellHistory -> [SQLData] |
insertShellHistory :: String -> String -> IO () Source #
Insert dot_bash_history to sqlite3
KEY: insert history, history sqlite3, insert .bash_history to sqlite3
- Need to create symlink to ~/.bash_history
home <- getEnv HOME hisFile = home / "myfilebitbucketshelldot_bash_history"
- drop ShellHistory table
- create table ShellHistory
- read dot_bash_history
- insert all cmds to ShellHistory
home <- getEnv HOME let dbfile = home / "myfilebitbucketdatabase/ShellHistory.db" >sqlite3 dbfile >.table >SELECT * FROM ShellHistory
- Sqlite3 Table:
ShellHistory
- Construct sql query in
Query
type as following - Use
toSText
to convertString
toText
- See Query
data Query = Query{fromQuery::TS.Text} insert_table = Query {fromQuery = toSText "INSERT INTO ShellHistory (shcmd) VALUES (?)"}
UPDATE: Wednesday, 17 November 2021 15:41 PST
hisdb = "myfilebitbucketdatabase/ShellHistory.db"
bashHis = "myfilebitbucketshell/dot_bash_history"
queryShellHistory :: String -> IO [String] Source #
filter out lines in history file
hisdb = "myfilebitbucketdatabase/ShellHistory.db" bashHis = "myfilebitbucketshell/dot_bash_history"
redisGet :: String -> IO (Maybe String) Source #
Redis get value
- Redis default Connection Info
defaultConnectInfo connectHost = "localhost" connectPort = PortNumber 6379 -- Redis default port connectAuth = Nothing -- No password connectDatabase = 0 -- SELECT database 0 connectMaxConnections = 50 -- Up to 50 connections connectMaxIdleTime = 30 -- Keep open for 30 seconds
Get Value from a key
It uses Default Connection
See redisSet
GHCi: redisSet "key1" "value1" redisGet "key1"
redisGetConn :: Connection -> String -> IO (Maybe String) Source #
Get value from Redis db
- Redis default Connection Info
defaultConnectInfo connectHost = "localhost" connectPort = PortNumber 6379 -- Redis default port connectAuth = Nothing -- No password connectDatabase = 0 -- SELECT database 0 connectMaxConnections = 50 -- Up to 50 connections connectMaxIdleTime = 30 -- Keep open for 30 seconds
redisSet :: String -> String -> IO () Source #
Redis set key value
Set key and value in Redis
It uses Default Connection
See redisGet
GHCi: redisSet "key1" "value1" redisGet "key1"
redisSetConn :: Connection -> String -> String -> IO () Source #
redisSetConnSByteString :: Connection -> ByteString -> ByteString -> IO () Source #
redisConnectDefault :: IO Connection Source #
redisDisconnect :: Connection -> IO () Source #
KEY: redis disconnect, destroy resource, destroy connection, destroy redis
conn <- redisConnectDefault RED.disconnect conn
checkCSSColorFormat :: Text -> Bool Source #
check CSS color format,
"#334455" => valid "#333" => valid "#1234567" => not valid
concatStyle :: [(String, String)] -> String Source #
concat style fields: ("color", "red") => "color:red;"
pf :: PrintfType r => String -> r Source #
C style printf, string format
- import Text.Prinf
printf::PrintfType => r -> s printf "%.2f" 3.0 3.00 let n = 3::Int let f = rf n printf "%.2f, %.2f" f f let name = "dog" let weight = 20 printf "(%s)=(%d)" "(dog)=(20)" let s = pf "%.2f" 3.1415 pp s c character Integral d decimal Integral o octal Integral x hexadecimal Integral X hexadecimal Integral b binary Integral u unsigned decimal Integral f floating point RealFloat F floating point RealFloat g general format float RealFloat G general format float RealFloat e exponent format float RealFloat E exponent format float RealFloat s string String v default format any type
(?) :: Bool -> a -> a -> a infix 1 Source #
KEY: ternary operator like c++, if else
let x = 3 in x > 3 ? "> 3" $ " < 3"
readConfig :: FilePath -> IO (HashMap String (HashMap String String)) Source #
Parse a text file and return HashMap String (HashMap String String)
- OS specific config file
Config file could have the following format. @
os = macOS
↑ + → os has to be in the file.
host = localhost path = /usr/home/user
os = linux
↑ + → os has to be in the file.
host = myhost path = /usr/home/user
return
HashMap String (HashMap String String) = [("macOS", (fromList [("host", "localhost"), ("path", "/usr/home/user")))]
* Update Fri Mar 13 21:52:36 2020 * Add skip comment code * Saturday, 24 September 2022 21:13 PDT * Update String with double quotes
- - comment
- - gf $bhaskellwebapp2config.txt host = localhost @
Use createConfigMap
instead
concatFile :: FilePath -> FilePath -> FilePath -> IO () Source #
concat two files to a thrid file
extractNumFromStr :: String -> Integer Source #
KEY: extract a first number from a string.
strToIntegerMaybe :: String -> Maybe Integer Source #
KEY: convert String
to Maybe
Integer
strToStrictByteString "12" => Just 12 strToStrictByteString "01" => Just 1 strToStrictByteString "00" => Just 0 strToStrictByteString " 1" => Nothing strToStrictByteString "1a" => Nothing
commentLine :: String -> String -> String Source #
commentCode :: String -> [String] -> [String] Source #
takeBetweenExc :: String -> String -> [String] -> [String] Source #
takeIndexBetweenInc :: (Int, Int) -> [a] -> [a] Source #
KEY: take elements between both indices
takeIndexBetweenInc (3, 4) [0..10] => [3, 4]
printBox :: Integer -> [String] -> IO () Source #
KEY: console ansi box, console textbox, ansi textbox, escape code, ascii code
See Ansi_Box_Drawing
-- BEG -- KEY: ansi color, console color import Rainbow import System.Console.Pretty (Color (..), Style (..), bgColor, color, style, supportsPretty) import qualified System.Console.ANSI as AN -- END -- move 4 tabs to the right printBox 4 ["dog", "cat"] ⌜-------⌝ |dog | |cat | ⌞-------⌟
printBoxColor :: Color -> Integer -> [String] -> IO () Source #
KEY: console ansi box, console textbox, ansi textbox
See Ansi_Box_Drawing
printBox
with Color
data System.Console.Pretty.Color = Black | Red | Green | Yellow | Blue | Magenta | Cyan | White | Default -- Defined in ‘System.Console.Pretty’ instance [safe] Enum System.Console.Pretty.Color -- Defined in ‘System.Console.Pretty’ -- BEG -- KEY: ansi color, console color import Rainbow import System.Console.Pretty (Color (..), Style (..), bgColor, color, style, supportsPretty) import qualified System.Console.ANSI as AN -- END -- move 4 tabs to the right printBox 4 ["dog", "cat"] ⌜-------⌝ |dog | |cat | ⌞-------⌟
printBoxColor2 :: Integer -> Integer -> [String] -> IO () Source #
splitWhileStr :: (Char -> Bool) -> String -> (String, String) Source #
getLineFlush :: IO String Source #
replaceFileLineNoRegex :: FilePath -> String -> String -> IO () Source #
KEY: replace line with NO Regex
NOTE: "a & b \" has issue use regex replace
file: x.x line 1 latexcode_replace123 line 2 replaceLineNoRegex "tmpx.x" "latexcode_replace123" "a & b \"
replaceLineNoRegexListTuple :: [String] -> [(String, String)] -> [String] Source #
runSh :: Text -> IO (ExitCode, Text, Text) Source #
Run shell command with Turtle lib
See runShell
(e2, so, si2) <- runSh $ toSText cmd if e2 /= ExitSuccess then let rcode = ReplyCode{rcmd="", rerror = si2, stdout=si2} replyJson = toSBS $ DA.encode $ rcode in response $ responseNothingBS replyJson else do pp so let replyCode = ReplyCode{rcmd="", rerror="", stdout= so} let replyJson = toSBS $ DA.encode $ replyCode response $ responseNothingBS replyJson
shellStrictWithErr :: MonadIO io => Text -- ^ Command line -> Shell ByteString -- ^ Chunks of bytes written to process input -> io (ExitCode, ByteString, ByteString) -- ^ (Exit code, stdout, stderr) shellStrictWithErr cmdline = systemStrictWithErr (Process.shell (Data.Text.unpack cmdline))
SEE: runShStr
runShStr :: String -> IO (ExitCode, String, String) Source #
KEY: run String command
(ExitCode, out, err) <- runShStr "grep error tmpa.x" if ExitCode == ExitSuccess then putStrLn out else putStrLn err
SEE: runSh
runRawCmd :: String -> [String] -> IO [String] Source #
Prevent shell expand argument variable, e.g '$1', '$2'
- KEY: shell not expand, shell literal, shell expand, shell escape variable, shell raw variable
runRawCmd "write_to_shell" ["cat $1 $2"] -- cat $1 $2
- Usage
runRawCmd "ls" [] runRawCmd "ls" ["-la"]
waitForProcess
to finish orexitFailure
Try to replace as many as shell command as possible
- shell ls command
- See how far I can go
- write many shell commands as possible
- try to emulate shell commands
- Sat Feb 1 23:40:55 2020
lsFile :: String -> IO [String] Source #
KEY: list file
- Sat Feb 1 22:25:09 2020
- FOUND ERROR: don't use the function, it creates zombie process
- Sun Feb 2 13:12:01 2020
- Fixed ERROR with
runRawCmd
- NOTE: Not a full path
- SEE:
lsFileFull
=> list full path - SEE:
lsStr
drawInt :: Int -> Int -> IO Int Source #
KEY: random Integer
- Generate Int from x to y random number
System.Random randomR :: (Random a, RandomGen g) => (a, a) -> g -> (a, g) ↑ ↑ + - - - - - - + | | + - - - - + | | System.Random getStdRandom :: MonadIO m => (StdGen -> (a, StdGen)) -> m a
lsFileFull :: String -> IO [String] Source #
KEY: list of FULL path files
lsFileFull
is NON recursive- See
lsFile
orrunRawCmd
- return full path files list
lsFileFull "." lsFileFull "/dog/cat"
- Sat Feb 1 22:25:09 2020
- FOUND ERROR: don't use the function, it creates zombie process
- Sat Feb 1 23:33:12 2020
- Fixed ERROR with
runRawCmd
- NOTE: list of full path
- See
lsFileFull
=> list full path
lsRegexFull :: String -> RegexStr -> IO [String] Source #
KEY: list full path with regex match, see lsRegex
, list file with filter, file filter, file path with regex
lsRegexFull "." "\\.hs$" lsRegexFull "/tmp" "\\.hs$"
lsFullRegex :: String -> RegexStr -> IO [String] Source #
Deprecated, use lsRegexFull
list full path with regex match
lsRegexFull "." "\\.hs" lsRegexFull "/tmp" "\\.hs"
writeFileStr :: FilePath -> String -> IO () Source #
KEY: write a string to file
Use writeFile
writeFile::FilePath -> String -> IO() writeFileStr = writeFile
writeFileOver :: FilePath -> String -> IO () Source #
Overwrite a file
writeFileList :: FilePath -> [String] -> IO () Source #
c2w_ :: Char -> Word8 Source #
Char to word8, char to int
- readFile to ByteString
ls <- BS.readFile "/tmp/b.x" lsBS = BS.split (c2w_ '\n') ls
intToString :: Integer -> String Source #
Convert Integer to string, int to str
>>>
intToString 123
"123"
integerToString :: Integer -> String Source #
Convert Integer to string, int to str
>>>
integerToString 123
"123"
integerToInt :: Integer -> Int Source #
Convert Integer to Int
Use fromInteger
intToCharDigit :: Int -> Char Source #
Int to digit char
intToCharDigit 3 => '3' intToCharDigit 31 => Exception
Use intToDigit
extractStr :: (Integer, Integer) -> String -> String Source #
Extract a string from a string
See extract
or Extract
class Extract source where before :: Int -> source -> source after :: Int -> source -> source extract:: (Int, Int) -> source -> source instance Extract String where extract :: (Int, Int) -> String -> String extractStr::(index, len) -> String -> String
integerToBinary :: Integer -> String Source #
charToDecimal :: Char -> Int Source #
charToDecimalInteger :: Char -> Integer Source #
charToIntX :: Char -> Int Source #
deprecated
NOTE: confusing naming Monday, 24 July 2023 12:09 PDT NOTE: DO NOT USE any more
deprecated
NOTE: confusing naming Monday, 24 July 2023 12:09 PDT NOTE: DO NOT USE any more
char0to9ToInt :: Char -> Int Source #
KEY: char digit to Int
integerToCharDigit :: Integer -> Char Source #
deprecated
stringToInteger :: String -> Integer Source #
Convert string to Integer, str to int, str to num, string to num
stringToInteger "123" 123 stringToInteger "a" error
- The Read class Text.Read
strToInteger :: String -> Integer Source #
String to Integer
alias of stringToInteger
stringToInt :: String -> Int Source #
KEY: Convert string to Integer, str to int, str to num, string to num, string to int
stringToInt "123" 123 stringToInt "a" error
Read
is a typeclass all the instance need to implement following method @ strToInteger :: String -> Integer strToInteger s = foldr (+) zipWith(x y -> (digitToInt x) * 10^10) (reverse s) [0..]class Read a where read :: String -> a
instance Read Integer where read s = strToInteger s @
read "123"::Int
strToInt :: String -> Int Source #
String to Int, str to Int
Same as stringToInt
pre :: (MonadIO m, Show a) => a -> m () Source #
KEY: pretty print
print tuple, print list, print two dimensions list print record print list of tuple use pPrint
[("a", "b"), ("c", "d")]
readFileLatin1ToList :: FilePath -> IO [String] Source #
use latin1
encoding to avoid error when reading non ASCII characters
URL: https://hackage.haskell.org/package/base-4.18.0.0/docs/System-IO.html#t:TextEncoding
FIXED: bug, read file contains unicode does not work properly. @ -- Monday, 24 July 2023 15:47 PDT -- DO NOT use latin1
latin1 :: TextEncoding utf8 :: TextEncoding
Change: hSetEncoding latin1 To hSetEncoding utf8 @
readFileList :: FilePath -> IO [String] Source #
Read a file and return a String
readFileStr :: FilePath -> IO String Source #
readFileDouble :: FilePath -> IO [[Double]] Source #
read file data, covert each line to [Double
] => [[Double
]]
tmpx.x 3.14 2.0 1.0 2.0 ls <- readFileDouble "tmpx.x" [[3.14, 2.0], [1.0, 2.0]]
readFileFloat :: FilePath -> IO [[Float]] Source #
read file data, covert each line to [Float
] => [[Float
]]
tmpx.x 3.14 2.0 1.0 2.0 ls <- readFileFloat "tmpx.x" [[3.14, 2.0], [1.0, 2.0]]
readFileInt :: FilePath -> IO [[Int]] Source #
read file data, covert each line to [Int
] => [[Int
]]
tmpx.x 3 2 1 2 ls <- readFileInt "tmpx.x" [[3, 2], [1, 2]]
timeNowPico :: IO Integer Source #
(round . (* 10^12)) <$> getPOSIXTime
timeNowNano :: IO Integer Source #
(round . (* 10^9)) <$> getPOSIXTime
timeNowMicro :: IO Integer Source #
(round . (* 10^3)) <$> getPOSIXTime
timeNowMilli :: IO Integer Source #
(round . (* 10^6)) <$> getPOSIXTime
timeNowSecond :: IO Integer Source #
Same as timeNowSec
(round . (* 1)) <$> getPOSIXTime
timeNowSec :: IO Integer Source #
Same as timeNowSecond
getLocalTime :: IO LocalTime Source #
get local time with TimeZone
getLocalTime
2020-07-08 12:14:46.10179
LocalTime
utcTime <- getCurrentTime z <- getCurrentTimeZone let utc = utcToLocalTime z utcTime return utc
getLocalDate :: IO String Source #
KEY: get local date, get current time
"2019-05-27 12:57:41.520758 PDT"
KEY: get local date, get current time
s <- getLocalDate putStr s 2019-05-27 12:57:41.520758 PDT
KEY: get local date, get current time
s <- dateStr putStr s 2019-05-27 12:57:41.520758 PDT
KEY: get local current time, local time, time zone
NOTE getCurrentTime
is UTC timezone only,
getTimeDay
time with day
return $ (show hour) ++ ":" ++ (show minute) ++ ":" ++ (show second)
trim :: String -> String Source #
Trim, remove whitespace characters from either side of string.
see trimWS
all whitespace
splitStr :: RegexStr -> String -> [String] Source #
KEY: split string, split str
NOTE: DOES NOT Support String contains unicode
> splitStr "25151" "abc25151def" > splitStr "::" "dog::cat" => ["dog", "cat"] > let s = "25151 abc 25151" "房 abc 房" > splitStr "25151" s *** Exception: user error (Text.Regex.Posix.String died: (ReturnCode 13,"repetition-operator operand invalid")) > splitWhen > splitWhenFirstNoRegex "25151" s Just (""," abc 25151")
splitStrChar :: RegexStr -> String -> [String] Source #
Partition string to [String] according to character class []
splitStrChar "[,.]" "dog,cat,cow.fox" => ["dog", "cat", "cow", "fox"]y splitStrChar::String->String->[String] splitStrChar r s = splitWhen(x -> matchTest rex (x:[])) s where rex = mkRegex r
- See
splitStrCharTrim
splitStrRegex => splitStrChar
splitStrCharTrim :: RegexStr -> String -> [String] Source #
Split String. trim
and Remove empty String
splitStrCharTrim "[,.]" " dog,fox. " => ["dog", "fox"]
- See
splitStrChar
matchAllBS :: ByteString -> ByteString -> [(MatchOffset, MatchLength)] Source #
Match all pat from a given str
len :: (Foldable t, Num b) => t a -> b Source #
Better length function
- Convert Int to polymorphic values
- Convert Int to Num
- fromIntegral::(Integral a, Num b)=> a -> b
splitStrTuple :: String -> String -> (String, String) Source #
split key and value
splitStrTuple "=" "host = localhost" => (host, localhost)
- TODO: fix the function if host = dog = cat => ("host", "dogcat")
logFileTmp :: [String] -> IO () Source #
logFileNoName :: [String] -> IO () Source #
logFileGEx :: Bool -> String -> [String] -> IO () Source #
logFileMat :: Show a => String -> [[a]] -> IO () Source #
logFileSBS2 :: FilePath -> [ByteString] -> IO () Source #
showIntAtBaseX :: Integral a => a -> (Int -> Char) -> a -> ShowS Source #
KEY: binary, octedecimal, hexadecimal, int to hexadecimal
See showIntAtBase
from Numeric
showIntAtBaseX 2 intToDigit 10 "" => binary showIntAtBaseX 8 intToDigit 10 "" => octal showIntAtBaseX 10 intToDigit 10 "" => decimal showIntAtBaseX 16 intToDigit 10 "" => hexadecimal -- hexadecimal to decimal showIntAtBaseX 10 intToDigit (hexToInt "ff") ""
integerToHex :: Integer -> String Source #
KEY: integer to hexadecimal
hexToInt :: String -> Integer Source #
KEY: Integer to hexadecimal
integerToHex::Integer -> String -- Use Numeric showInt integerToHex n = showInt n ""
KEY: hexadecimal to Integer
unescape :: String -> String Source #
KEY: escape char to unescape char, int to unicode
"\x2206" => "x2206"
intToUnicode :: Int -> Char Source #
KEY: int to unicode
hex: x2206 => ∆
hexToUnicode :: String -> Char Source #
KEY: hexadecimal to unicode
data FrameCount Source #
FrameCount | |
|
Instances
Eq FrameCount Source # | |
Defined in AronModule (==) :: FrameCount -> FrameCount -> Bool (/=) :: FrameCount -> FrameCount -> Bool | |
Show FrameCount Source # | |
Defined in AronModule showsPrec :: Int -> FrameCount -> ShowS show :: FrameCount -> String showList :: [FrameCount] -> ShowS |
resetRefFrame :: IORef FrameCount -> IO () Source #
readRefFrame2 :: IORef FrameCount -> Integer -> IO (Int, Bool, FrameCount) Source #
KEY: animate counter
(count, isNext, currRef) <- readRefFrame2 refCount 200 refFrame (timeNowMilli>= x -> newIORef FrameCount{frameTime = x, frameCount = 1}) (count, isNext, currRef) <- readRefFrame refFrame -- count => start from 1 to 100, 1 <= count <= 100 and stop at 100 -- isNext => Bool, the delay is <= 20::Integer then True else False -- currRef => old Ref or updated Ref dependen on whether isNext is True or False when isNext $ do draw1 draw2
fileSizeStrToNum :: String -> Float Source #
KEY: file size unit, Kilobyte or Magebyte NOT Gigabyte, Terabyte or Petabyte
fileSizeStrToNum 31M => 31 * 1024 fileSizeStrToNum 20K => 20
whichGetPath :: String -> IO FilePath Source #
KEY: which in shell, which pdflatex
openFileUtf8 :: MonadIO m => FilePath -> IOMode -> m Handle Source #
readFileUtf8 :: MonadIO m => FilePath -> m Text Source #
scientificToFloat :: RealFloat a => Int -> a -> String Source #
scientific notation to normal notation
- package:
Numeric
showFFloat
scientificToFloat
scientificToFloat 3 3.1415e-2 -- 0.031 sciToFloat 3 3.1415e-2 -- 0.031 showFFloat (Just 3) 3.1415e-2 "" -- 0.031
sciToFloat :: RealFloat a => Int -> a -> String Source #
scientific notation to normal notation
- package:
Numeric
showFFloat
scientificToFloat
scientificToFloat 3 3.1415e-2 -- 0.031 sciToFloat 3 3.1415e-2 -- 0.031 showFFloat (Just 3) 3.1415e-2 "" -- 0.031
colorfgStr :: Integer -> String -> String Source #
KEY: Terminal color, term color, term background color, shell color, escape code sequence
http://localhost/html/indexTerminalColorandEscapeCodeSequence.html
colorfgStr::Integer -> String -> String -- putStrLn $ colorfgStr 200 Hello colorfgStr n s = fg ++ color ++ s ++ reset where fg = "x1b[38;5;" color = (show n) ++ "m" reset = "x1b[0m"
Use 256 Colors in terminal Set foreground color: x1b[38;5; {color code}m x1b[0m Set background color: x1b[48;5; {color code}m x1b[0m | | | | | |-> reset color | |-> RGB color (0-255) | |-> 38 => foreground |-> 48 => background 24 bit RGB (Truecolor) {r} {g} {b} 8bits 8bits 8bits = 24bits 32 bit RGBA {r} {g} {b} {a} 8bits 8bits 8bits 8bits 2^10 = 1024 2^5 = 32 x 32 = 940 + 64 = 1024 2^24 = (2^10)^2 * 2^2 = 1024 x 1024 = 1M*2^2 = 4M Set foreground color: x1b[38;2;{r};{g};{b}mx1b[0m Set background color: x1b[48;2;{r};{g};{b}mx1b[0m | | | | | |-> reset color | |-> RGB color (0-255) | |-> 38 => foreground |-> 48 => background putStrLn $ colorfgStr 200 Hello
SEE: color
Pretty
colorbgStr :: Int -> String -> String Source #
KEY: Terminal color, term color, term background color, shell color, color background string
putStrLn $ colorbgStr 200 "Hello"
colorbgStr::Int -> String -> String -- putStrLn $ colorbgStr 200 Hello colorbgStr n s = bg ++ color ++ s ++ reset where bg = "x1b[48;5;" color = (show n) ++ "m" reset = "x1b[0m" -- Use AronToken let s = "( 1 + 2 = 3 )" putStr $ (concat . colorToken) $ tokenize s
SEE: AronToken
SEE: tokenize
colorToken
SEE: colorfgStr
SEE: color
Pretty
createProcessPipeData :: String -> [String] -> String -> IO (Maybe Handle, ExitCode) Source #
KEY: pipe data to external process
ls = ["dogn", "catn"]
|
|
↓
pipe | createPipe
|
↓
External Process
"alignmentStr -p kk"
|
↓
Handle = hout
|
↓
hGetContents hout
|
↓
putStr
let ls = [""12"", ""34 "", ""5 6 ""]
mayStOut <- createProcessPipeData "alignmentStr" ["-p", "kk"] ls
case mayStOut of
Just hout -> hGetContents hout >>= x -> length x seq
putStr x
_ -> putStrLn "nothing"
writeFileSText :: FilePath -> Text -> IO () Source #
KEY: write Strict Text to file
writeFileLText :: FilePath -> Text -> IO () Source #
KEY: write Lazy Text to file
pad :: Num a => Int -> a -> [a] -> [a] Source #
KEY: padding zero to a list
Thu 2 Nov 12:06:19 2023 NOTE: disable it because Arrow use the same operator
KEY: padding zero to a list
padding left >pad 2 0 [1, 2]
padding right >pad (-2) 0 [1, 2]
shiftMatrixLeft :: Num a => Int -> [[a]] -> [[a]] Source #
KEY: shift each row of matrix to left and padding with zero
let m = [[1, 2, 3] ,[3, 4, 5] ,[6, 7, 8]] let shiftMat = shiftMatrixLeft 3 m
shellHighlight :: String -> [String] Source #
- - data System.Console.Pretty.Color
- - = Black
- - | Red
- - | Green
- - | Yellow
- - | Blue
- - | Magenta
- - | Cyan
- - | White
- - | Default
- -
blockBegEnd :: (String -> Bool) -> (String -> Bool) -> [String] -> [[String]] Source #
pick :: (a -> Bool) -> [a] -> ([a], [a]) Source #
KEY: pick from a list
let (optls, numls) = pick (hasStr "-") ["-n", "-f", "10", "1", "5"] optls = ["-n", "-f" numls = ["10", "1", "5"]
containAll :: Ord a => [a] -> [a] -> Bool Source #
KEY: Check cx within cy
containAll [1, 2], [1, 2, 3] => True
combin :: Int -> [a] -> [[a]] Source #
KEY: m choose n, combination
URL: https://wiki.haskell.org/99_questions/Solutions/26
L.tails = mytails
mytails :: [a] -> [[a]] mytails [] = [[]] mytails (x:cx) = (x:cx):(mytails cx) mytails [1, ll2, 3] [[1, 2, 3], [2, 3], [3]] combin 2 [1, 2, 3] [[1,2],[1,3],[2,3]] tails [1, 2, 3] [1, 2, 3], [2, 3], [3], [] Explanation: 1 2 3 4 1 2 3 4 2 3 4 3 4 4 [] 1 (c(n-1)) 2 (c(n-1)) 3(c(n-1)) 4(c(n-1)) 2 3 4 3 4 4 3 4 4 4
drawRectBar :: (Pixel px, PrimMonad m) => MutableImage (PrimState m) px -> (Int, Int) -> (Int, Int) -> Int -> [Int] -> px -> m () Source #
histogram :: FilePath -> IO () Source #
KEY: draw histogram from a file
tmpx.x 1 3 9 20 14 histogram tmpx.x
insertIndexAt :: Int -> a -> [a] -> [a] Source #
KEY: insert to the next index
SEE removeIndex
removeFirstList :: Ord a => a -> [a] -> [a] Source #
KEY: remove the FIRST match from a list NOTE: Better name
removeFromList :: Ord a => a -> [a] -> [a] Source #
NOTE: Deprecated, bad name
USE: removeFirstList
readFileInteger2d :: FilePath -> IO [[Integer]] Source #
KEY: read file 2d string to integer
Write APL data to file and read it from it
m ← 3 3 3 ⍴ 10 ? 10 m 8 10 5 2 3 1 7 4 9 6 8 10 5 2 3 1 7 4 9 6 8 10 5 2 3 1 7 (⊂↓⎕FMT m) ⎕NPUT 'tmpx' ⎕cmd 'cat tmpx' File: 1 2 3 3 4 5 3 4 5 3 3 9 => [[Integer]]
readFileFloat2d :: FilePath -> IO [[Float]] Source #
KEY: read file 2d string to Float
Write APL data to file and read it from it
mf ← 3 3 3 ⍴ ? 10 ⍴ 0 mf 0.875658736 0.4130345348 0.7661493221 0.05092898876 0.7344701699 0.5883291622 0.08133906822 0.6499611783 0.203398563 0.7316870476 0.875658736 0.4130345348 0.7661493221 0.05092898876 0.7344701699 0.5883291622 0.08133906822 0.6499611783 0.203398563 0.7316870476 0.875658736 0.4130345348 0.7661493221 0.05092898876 0.7344701699 0.5883291622 0.08133906822 (⊂↓⎕FMT mf)⎕NPUT'tmpy' File: 1.1 2.0 3.1 2.1 3.3 3.3 2.1 3.3 3.3 => [[Float]]
alignTable :: [String] -> [[String]] Source #
KEY: alignment, column table, align column, format table
table 1: "a b c" "e f g" ↓ table 1: "a" "b" "c" "e" "f" "g"
columnTable :: [String] -> [[String]] Source #
KEY: alignment, column table, align column, format table
table 1: "a b c" "e f g" ↓ table 1: "a" "b" "c" "e" "f" "g"
trimList :: [String] -> [String] Source #
trim list of String
["", "", "a", " b ", " "] => ["a", "b"]
trimListST :: [Text] -> [Text] Source #
stepList :: [a] -> Int -> [([a], [Int])] Source #
KEY: Generate a step list
SEE: splitWhenFirstNoRegex
and splitWhenLastNoRegex
stepList "abcd" 2 ⟹ [ ( "ab" , [ 0 , 1 ] ) , ( "bc" , [ 1 , 2 ] ) , ( "cd" , [ 2 , 3 ] ) ]
splitWhenFirstNoRegex :: String -> String -> Maybe (String, String) Source #
KEY: split a string without Regex, String can contain unicode
> splitWhenFirstNoRegex "=" "25151 abc
=123=456" Just ("25151 abc","123
=456") > splitStr "25151" "abc25151def" > let s = "25151 abc 25151" "房 abc 房" > splitStr "25151" s *** Exception: user error (Text.Regex.Posix.String died: (ReturnCode 13,"repetition-operator operand invalid")) > splitWhen > let s = "25151 abc 25151" > splitWhenFirstNoRegex "25151" s Just (""," abc 25151")
splitWhenLastNoRegex :: String -> String -> Maybe (String, String) Source #
KEY: split a string without Regex, String can contain unicode
- Use
stepList
> splitWhenLastNoRegex "=" "25151 abc
=123=456" Just ("25151 abc
=123","456")
splitStrCharNoRegex :: String -> String -> [String] Source #
KEY: Split String to a list
pre $ splitStrCharNoRegex "NUL" "123NULabcd0efghNUL" [ "123" , "abcd" , "efgh" ] pre $ splitStrCharNoRegex "0" "123NULabcd0efghNUL" [ "123" , "abcd" , "efgh" ]
frequenceCount :: Ord a => [a] -> [(a, Int)] Source #
KEY: count the frequence of items
SEE: groupBy
SEE: 'L.groupBy . sort'
@
frequenceCount ["a", "b", "a", "b", "c"]
[("a",2),
("b",2),
("c",1)]
frequenceCount [1, 2, 1, 3] [(1, 2), (2, 1), (3, 1)] @
DropHead | |
DropLast | |
DropIndex Int | |
PrintIndex Int | |
PrintHead | |
PrintLast | |
PrintAll | |
Append String | |
AppendList [String] | |
Prepend String | |
NumberOfBlock |
fileBlock :: FilePath -> String -> FileBlock -> IO () Source #
KEY: Monday, 17 July 2023 14:55 PDT FIXED: Make delimiter and separator are the same.
splitPrefix :: (a -> Bool) -> [a] -> ([a], [a]) Source #
KEY: split prefix
let t
(h, t) = splitPrefix (x -> x /= ' ') ":abcd efgh ijkl mnop qrst uvwx yz"
(":abcd"," efgh ijkl mnop qrst uvwx yz")
NOTE:break == splitPrefix break (== ' ') ":ab c" => (":ab", " c") @
breakFirst :: (a -> Bool) -> [a] -> ([a], [a]) Source #
grepx :: ByteString -> FilePath -> IO () Source #
KEY: grep, iostream
NOTE: does not work inside GHCi URL: https://www.reddit.com/r/haskellquestions/comments/154y4x7/comment/jsyv1e9/?context=3
grepLine :: FilePath -> (String -> Bool) -> IO () Source #
KEY: it is based on stream library
https://hackage.haskell.org/package/io-streams-1.5.2.2/docs/System-IO-Streams-Tutorial.html NOTE: does not work so far URL: https://www.reddit.com/r/haskellquestions/comments/154y4x7/comment/jsyv1e9/?context=3
clipBoardcp :: String -> IO () Source #
KEY: clipboard, pbcopy, pbpaste, copy and paste
clipBoardpa :: IO [String] Source #
getContentsCTRLD :: IO String Source #
KEY: ghci read line
- read line inside GHCi
NOTE: CTRL-D => GHCi => EOT
hasSubstr :: String -> String -> Bool Source #
print $ hasSubstr "ab" "xxabb" == True print $ hasSubstr "axb" "xxabb" == False print $ hasSubstr "" "xxabb" == True print $ hasSubstr "xab" "xxabb" == True
hasStrBlock :: String -> [String] -> [[String]] Source #
hasStrBlock "abc" ["abc", "kk", "--", "aaa"] [["abc", "kk"] ["aaa"]]
powerSet :: [a] -> [[a]] Source #
KEY: power set, powerset
[] => [[]] [1] => (x:[]) [[1]] ++ [[]] => [[], [1]] [1,2] => (1:[2]) => map (1:) $ [[],[2]) ++ [[], [2]] => [[1],[1,2]] ++ [[], [2]] => [[], [1], [2], [1,2]]
printMat3 :: Show a => IOArray (Int, Int, Int) a -> IO () Source #
KEY: print array, print 2d array
let a = 1; b = 2; c = 3 ls <- DAO.newListArray ((0, 0, 0), (a, b, c)) [1..((a + 1) * (b + 1)) * (c + 1)] :: IO(IOArray (Int, Int, Int) Int) printMat3 ls
printMat2 :: Show a => IOArray (Int, Int) a -> IO () Source #
KEY: print array, print 3d array
let a = 2; b = 3 ls <- DAO.newListArray ((0, 0), (a, b)) [1..((a + 1) * (b + 1))] :: IO(IOArray (Int, Int) Int) printMat2 ls
cap :: IO a -> IO String Source #
KEY: capture stdout from print
Silently
fromsilently
package fun :: IO() fun = print "capture string" str <- capture_ $ fun print str
readAndParse :: Read a => FilePath -> IO a Source #
KEY: read file and convert to Haskell type
(x, y) <- readAndParse "tmpa" :: IO (Float, Float)
readMaybeParse :: Read a => FilePath -> IO (Maybe a) Source #
multiMatArr :: (Ix a, Ix b, Ix c, Num n) => Array (a, b) n -> Array (b, c) n -> Array (a, c) n Source #
NOTE: The runtime is very slow SEE: RunTime
-- https://www.haskell.org/tutorial/arrays.html let ln = 500 m1 geneRandMat (ln, ln) <& join let ar1 = array ((0, 0),(ln - 1, ln - 1)) [((i, j), let ix = i * ln + j in m1 !! ix) | i <- range (0, ln - 1), j <- range (0, ln - 1)] let a0 = array ((0, 0), (1, 1)) [((i, j), i + j) | i <- range (0, 1), j <- range (0, 1)] let a1 = array ((0, 0), (1, 1)) [((i, j), i + j) | i <- range (0, 1), j <- range (0, 1)] let m = multiMatArr a0 a1 print a0 fw "" print a1 fw "m" print m fw "ar1 x ar1" old <- timeNowMicro let m2 = multiMatArr ar1 ar1 wfl "tmpx.x" $ map show $ elems m2 new <- timeNowMicro let diff = new - old fw "diff=" print diff
compareArray :: [Int] -> [Int] -> Int Source #