* 꼬리 재귀호출과 패턴 매칭을 이용하여 구현한 팩토리얼과 피보나치 수열 계산

{-
    Filename: fact.hs
         Rapid factorial and fibonacci seq implementations
         by pattern matching and tail recursive call

    Compile: ghc fact.hs
    Execute: main

    Date: 2010/07/20
    Author: phkim  pkim (AT) scripts.pe.kr
-}

module Main where

  factorial :: Integer -> Integer
  factorial n =  recfact 1 n

  recfact :: Integer -> Integer -> Integer
  recfact acc k = case k of
        0 -> acc
        k-> recfact (acc*k) (k - 1)

  fib :: Integer -> Integer
  fib n = fibGen 0 1 n

  fibGen :: Integer -> Integer -> Integer -> Integer
  fibGen a b n = case n of
        0 -> a
        n -> fibGen b (a + b) (n - 1)

  main :: IO ()
  main = do
        print ("Factorial(30000) has " ++ show (length (show (factorial 30000))) ++ " digits")
        print ("Fibonacci(200000) has " ++ show (length (show (fib 200000))) ++ " digits")

{-
    Expected result:
    "Factorial(30000) has 121288 digits"
    "Fibonacci(200000) has 41798 digits"
-}



크리에이티브 커먼즈 라이선스
Creative Commons License

 

Posted by Scripter
,

F# 언어에서 int 타입과 bigint 타입을 상호변환 하는 것은 의외로 쉽다.


명령 프롬프트> fsi

Microsoft (R) F# 2.0 Interactive build 2.0.0.0
Copyright (c) Microsoft Corporation. All Rights Reserved.

For help type #help;;
> let a = 100I;;
val a : System.Numerics.BigInteger = 100I

> let b = int a;;
val b : int = 100

> let c = bigint b;;
val c : System.Numerics.BigInteger = 100I
> b**5;;
  b**5;;
  ^
stdin(13,1): error FS0001: The type 'int' does not support any operators named '
Pow'

> a**5;;
val it : System.Numerics.BigInteger = 10000000000I

> c**5;;
val it : System.Numerics.BigInteger = 10000000000I

> a**5 = c**5;;
val it : bool = true

let k = int "320";;
val k : int = 320

> let m = bigint "320";;

  let m = bigint "320";;
  --------^^^^^^^^^^^^

stdin(19,9): error FS0041: No overloads match for method 'BigInteger'. The avail
able overloads are shown below (or in the Error List window).
Possible overload: 'System.Numerics.BigInteger()'.
Possible overload: 'new : x:int -> System.Numerics.BigInteger'.
Possible overload: 'new : x:int64 -> System.Numerics.BigInteger'.
Type constraint mismatch. The type
    string
is not compatible with type
    int
The type 'string' is not compatible with the type 'int'
Type constraint mismatch. The type
    string
is not compatible with type
    int64
The type 'string' is not compatible with the type 'int64'

> let m = new System.Numerics.BigInteger("320");;

  let m = new System.Numerics.BigInteger("320");;
  --------^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

stdin(22,9): error FS0041: No overloads match for method 'BigInteger'. The avail
able overloads are shown below (or in the Error List window).
Possible overload: 'System.Numerics.BigInteger()'.
Possible overload: 'new : x:int -> System.Numerics.BigInteger'.
Possible overload: 'new : x:int64 -> System.Numerics.BigInteger'.
Type constraint mismatch. The type
    string
is not compatible with type
    int
The type 'string' is not compatible with the type 'int'
Type constraint mismatch. The type
    string
is not compatible with type
    int64
The type 'string' is not compatible with the type 'int64'

> let m = "320" |> System.Numerics.BigInteger.Parse;;
val m : System.Numerics.BigInteger = 320I


크리에이티브 커먼즈 라이선스
Creative Commons License

 

Posted by Scripter
,


정의 (소수와 합성수)
    1보다 큰 양의 정수 n에 대하여
    (i) n = a * b 를 만족하고 1보다 큰 두 양의 정수 a와 b가 존재하면,
        n을 합성수(合成數, composite number)라고 한다. 참고로 이 경우,
        a, b 중에 적어도 하나는 sqrt(n) 보다 작거나 같다.
        합성수의 예로는 4, 6, 9, 24, 143 등이 있다.
    (ii) n = a * b 를 만족하고 1보다 큰 두 양의 정수 a와 b가 존재하지 않으면,
         즉 n을 두 양의 정수의 곱으로 표현하는 방법이 1*n과 n*1 두 가지 뿐이면,
         n을 소수(素數, prime number)라고 한다.  소수의 예로는 2, 3, 5, 7, 11 등이 있다.
         n이 소수인지 아닌지 확인하려면, 
         n을 2 보다 크거나 같고 sqrt(n) 보다 작거나 같은 모든 정수로 나누어 본다.
         이 경우 언제나 나누어 떨어지지  않으면 n은 소수이고, 그렇지 않으면 n은 합성수이다.
    

우선 다음의 F# 소스 코드는 명령행 인자로 전달 받은 양의 정수 n을
2 및 3, 5, 7, ... , sqrt(n) 이하의 홀수들로 나누어 보아 n이 합성수인지 아닌지
확인하는 애플리케이션 소스이다. 확인하는데 걸린 경과 시간도 알려준다.

(*
 *  Filename: DivideEach.fs
 *
 *  Purpose:  Determine whether the given integer is a prime or not.
 *
 *  Compile: fsc DivideEach.fs
 *  Execute: DivideEach [integer]
 *
 *     Date:  2010/07/17
 *   Author:  PH Kim   [ pkim ((AT)) scripts.pe.kr ]
 *)

(*
  Execution Examples:
      Prompt> DivideEach 1234567812343
      1234567812343 = 1 * 1234567812343
      1234567812343 is a prime
      Elapsed time: 0.750000 sec

      Prompt> DivideEach 9999994200000841
      9999994200000841 = 99999971 * 99999971
      9999994200000841 is a not prime
      Elapsed time: 121.140000 sec

      Prompt> DivideEach 18446744073709551617
      18446744073709551617 = 274177 * 67280421310721
      18446744073709551617 is a not prime
      Elapsed time: 0.218000 sec

      Prompt> DivideEach 10023859281455311421
      10023859281455311421 = 1308520867 * 7660450463
      10023859281455311421 is a not prime
      Elapsed time: 1471.500000 sec
/*)


#light

open System

let mutable n = 10006099720301I

// Begin here
let cmdArgs = System.Environment.GetCommandLineArgs()
if (Array.length cmdArgs > 1) then
    // n <- new Numerics.BigInteger(cmdArgs.[1])
    n <- (cmdArgs.[1]) |> Numerics.BigInteger.Parse


let mutable z = n / 2I
if n = 2I*z then
    printfn "%O = %O * %O" n  2I z

let time1 = DateTime.UtcNow

let mutable d = 1I
let mutable k = 3I
let mutable cont_flag = true
while (k*k <= n && cont_flag) do
    z <- n / k
    if n = k*z then
        d <- k
        cont_flag <- false
    else
        k <- k + 2I

let time2 = DateTime.UtcNow
let elapsed = float (int64 (time2 - time1).TotalMilliseconds) / 1000.0

printfn "%O = %O * %O" n d (n/d)
if d = 1I then
    printfn "%O is a prime" n
else
    printfn "%O is a not prime" n

printfn "Elapsed time: %f sec" elapsed



이제 다음은 정수의 인수분해 능력이 뛰어난  Pollard의 rho 방법(일명 거북이와 토끼 알고리즘, tortoise-hair algorithm)을 구현한  F# 소스 코드이다. 이 알고리즘은 소수에 대해서는 시간이 많이 걸리지만, 합성수에 대해서는 시간이 매우 적게 걸린다는 것이 특징이다.

(*
 *  Filename: PollardRho.fs
 *
 *  Purpose:  By using the pollard rho method,
 *            determine whether the given integer is a prime or not.
 *
 *      See:  http://en.wikipedia.org/wiki/Pollard%27s_rho_algorithm
 *            http://en.wikipedia.org/wiki/Floyd%27s_cycle-finding_algorithm#Tortoise_and_hare#
 *
 *  Compile: fsc PollardRho.fs
 *  Execute: PollardRho [integer]
 *
 *     Date:  20010/07/18
 *   Author:  PH Kim   [ pkim ((AT)) scripts.pe.kr ]
 *)

(*
  Execution Examples:
      Prompt> PollardRho 1234567812343
      Try first the Pollard rho algorithm with c = 2
      d = 1234567812343, count = 466951
      Try second the Pollard rho algorithm with c = 3
      d = 1, count = 1111112
      Try third the Pollard rho algorithm with c = 1
      d = 1234567812343, count = 799441
      1234567812343 = 1234567812343 * 1
      Elapsed time: 63.640000 sec

      Prompt> PollardRho 9999994200000841
      Try first the Pollard rho algorithm with c = 2
      d = 99999971, count = 3593
      9999994200000841 = 99999971 * 99999971
      Elapsed time: 0.281000 sec

      Prompt> PollardRho 18446744073709551617
      Try first the Pollard rho algorithm with c = 2
      d = 274177, count = 1028
      18446744073709551617 = 274177 * 67280421310721
      Elapsed time: 0.187000 sec

      Prompt> PollardRho 10023859281455311421
      Try first the Pollard rho algorithm with c = 2
      d = 1308520867, count = 20350
      10023859281455311421 = 1308520867 * 7660450463
      Elapsed time: 0.968000 sec
*)


#light

open System

let f (x : bigint) (c : bigint) (n : bigint) =
    (x*x + c) % n

let g (x : bigint) (c : bigint) (n : bigint) =
    f (f x c n) c n

let gcd x  y =
    let mutable a = abs x
    let mutable b = abs y
    if b = 0I then
        a
    else
        while b <> 0I do
            let t = a % b
            a <- b
            b <- t
        a

let pollardRho (n : bigint) =
    let mutable c = 2I
    let mutable x = 1I
    let mutable y = 1I
    let mutable d = 1I
    let mutable savedX = x
    let mutable count = 0I
    printfn "Try first the Pollard rho algorithm with c = %O" c
    let mutable cont_flag = true
    while d = 1I && count*count <= n && cont_flag do
        x <- f x c n
        if x = savedX then
            printfn "It is cyclic.  x = %O" x
            cont_flag <- false
        else
            y <- g y c n
            d <- gcd (abs (x - y)) n
        count <- count + 1I

    printfn "d = %O, count = %O" d count
    if d > 1I && d < n then
        d
    else
        c <- 3I
        x <- 1I
        y <- 1I
        d <- 1I
        savedX <- x
        count <- 0I
        printfn "Try second the Pollard rho algorithm with c = %O" c
        cont_flag <- true
        while d = 1I && count*count <= n do
            x <- f x c n
            if x = savedX then
                 printfn "It is cyclic.  x = %O" x
                 cont_flag <- false
            else
                 y <- g y c n
                 d <- gcd (abs(x - y)) n
                 count <- count + 1I

        printfn "d = %O, count = %O" d count
        if d > 1I && d < n then
            d
        else
            c <- 1I
            x <- 1I
            y <- 1I
            d <- 1I
            savedX <- x
            count <- 0I
            printfn "Try third the Pollard rho algorithm with c = %O" c
            let mutable cont_flag2 = true
            while d = 1I && count*count <= n do
                x <- f x c n
                if x = savedX then
                    printfn "It is cyclic.  x = %O" x
                    cont_flag2 <- false
                else
                    y <- g y c n
                    d <- gcd (abs(x - y)) n
                    count <- count + 1I

            printfn "d = %O, count = %O" d count
            d


// Begin here
let mutable n = 9991I

let cmdArgs = System.Environment.GetCommandLineArgs()
if (Array.length cmdArgs > 1) then
    n <- (cmdArgs.[1]) |> Numerics.BigInteger.Parse

let time1 = DateTime.UtcNow
let k = pollardRho n
let time2 = DateTime.UtcNow
let elapsed = float (int64 (time2 - time1).TotalMilliseconds) / 1000.0

let z = n/k
if n = k*z then
    printfn "%O = %O * %O" n k z

printfn "Elapsed time: %f sec" elapsed


 

Posted by Scripter
,


[파일명:  TestStringFindInList.fs]------------------------------------------------
#light

let find arr s = List.findIndex (fun x -> x = s) arr

let printList data =
    let rec loop l =
        match l with
        | x::[] -> printf "%O" x
        | x::xs -> printf "%O, " x; loop xs
        | [] -> printf ""
    printf "["
    loop data
    printf "]"

// Begin here
let cmdArgs = System.Environment.GetCommandLineArgs()

let words = ["하나"; "둘"; "셋"; "넷"; "다섯"; "여섯"]

printf "list: "
printList words
printfn ""
let where1 = find words "셋"
if where1 >= 0 then
    printf "발견!  "
    printf "Next word of 셋 in list: %O" (words.[where1+1])
printfn ""

printfn "Sorting..."
let otherwords = words |> List.sort |> List.sort

printf "list: "
printList otherwords
printfn ""
let where2 = find otherwords "셋"
if where2 >= 0 then
    printf "발견!  "
    printf "Next word of 셋 in list: %O" (otherwords.[where2+1])
printfn ""
------------------------------------------------


컴파일> fsc --codepage:949 TestStringFindInList.fs

실행> TestStringFindInList
list: [하나, 둘, 셋, 넷, 다섯, 여섯]
발견!  Next word of 셋 in list: 넷
Sorting...
list: [넷, 다섯, 둘, 셋, 여섯, 하나]
발견!  Next word of 셋 in list: 여섯


Posted by Scripter
,

printList 함수를 F#의 함수형 언어의 특징을 살려 (꼬리 재귀호출과 match 표현을 이용하여) 구현하였다.

[파일명:  TestSort.fs]------------------------------------------------
#light

let printList data =
    let rec loop l =
        match l with
        | x::[] -> printf "%O" x
        | x::xs -> printf "%O, " x; loop xs
        | [] -> printf ""
    printf "["
    loop data
    printf "]"

// Begin here
let cmdArgs = System.Environment.GetCommandLineArgs()
let b = cmdArgs.[1..] |> Array.toList |> List.sort
printList b
------------------------------------------------


컴파일> fsc TestSort.fs

실행> TestSort one two three four five
[five, four, one, three, two]

실행> TestSort 하나 둘 셋 넷 다섯
[넷, 다섯, 둘, 셋, 하나]

 

Posted by Scripter
,


초등학교 때 배우던 두 정수의 곱셈표를 만들어 주는 F# 소스이다.
이 소스는 Python 소스를 F# 소스로 변환한 것이라 F#의 명령형 언어 특징을 위주로 짜여져 있다.

(*
 * Filename: MakeMultTable.fs
 *
 *     Print a multiplication table.
 *
 *  Compile: fsc MakeMultTable.fs
 *  Execute: MakeMultTable 230 5100
 *
 *     Date: 2010/07/15
 *   Author:  PH Kim   [ pkim ((AT)) scripts.pe.kr ]
 *)

#light

exception RuntimeError of string
exception ValueError of string

let println s =
    printfn "%O" s

let print s =
    printf "%O" s

let printUsage dummy =
    println "Using: python makeMultTable.py [number1] [number2]"
    println "Print a multiplication table for the given two integers."

let printMultTable x y =
    let mutable nx = x
    if nx < 0 then
        nx <- -nx
    let mutable ny = y
    if ny < 0 then
        ny <- -ny
    let mutable ntail1 = 0
    let mutable ntail2 = 0
    while (nx % 10) = 0 do
        nx <- nx / 10
        ntail1 <- ntail1 + 1
    while ny % 10 = 0 do
        ny <- ny / 10
        ntail2 <- ntail2 + 1
    let z = nx * ny
    let strZ = sprintf "%d" z
    let strX = sprintf "%d" nx
    let strY = sprintf "%d" ny
    let n = strY.Length
    let zeros  = "0000000000000000000000000000000000000000"
    let whites = "                                        "
    let bars   = "----------------------------------------"
    let loffset = "       "
    let line4 = loffset + strZ
    let line1 = loffset + (whites.Substring(0, strZ.Length - strX.Length)) + strX
    let line2 = "   x ) " +  (whites.Substring(0, strZ.Length - strY.Length)) + strY
    let line3 = "     --" +  (bars.Substring(0, strZ.Length))
    println (line1 + (zeros.Substring(0, ntail1)))
    println (line2 + (zeros.Substring(0, ntail2)))
    println line3
    if strY.Length > 1 then
        for i in 0..(strY.Length - 1) do
            let y1 = int (strY.Substring(strY.Length - i - 1, 1))
            if not (y1 = 0) then
                let strT = sprintf "%d" (nx * y1)
                println (loffset + (whites.Substring(0, strZ.Length - strT.Length - i)) + strT)
        println line3
    println (line4 + (zeros.Substring(0, ntail1)) + (zeros.Substring(0, ntail2)))

// Begin here
let cmdArgs = System.Environment.GetCommandLineArgs()
if (Array.length cmdArgs >= 3) then
    let x = int (cmdArgs.[1])
    let y = int (cmdArgs.[2])
    println ""
    printMultTable x y
else
    printUsage 0
    exit(1)





컴파일> fsc MakeMultTable.fs

실행> MakeMultTable 230 5100
결과>

         230
   x )   5100
     ------
         23
       115
     ------
       1173000

 

 

 

Posted by Scripter
,
▒ F#  소스:  TestStringReverse.fs

#light

let a = "Hello, world!"
let b = "안녕하세요?"
let mutable arr = a.ToCharArray()
arr <- Array.rev arr
System.Console.WriteLine(new System.String(arr))
arr <- b.ToCharArray()
arr <- Array.rev arr
System.Console.WriteLine(new System.String(arr))

(*
Expected result:
!dlrow ,olleH
?요세하녕안
*)




주: 한글이 출력되어야 하므로 fsc 명령으로 컴파일시 옵션 --codepage:949 를 추가한다.




 

Posted by Scripter
,

다음은 초등학교에서 배우는 나눗셈 계산표를 만들어주는 F# 소스 코드이다.
나눗셈 계산표를 완성하고 나서 약수, 배수 관계를 알려준다.

아래의 소스는 Python 용 소스를 F# 용 소스로 거의 일대일 변환한 것이라서, F# 언어의 명령형 언어의 특징을 위주로 짜여져 있다.

  1. (*
  2.  *  Filename: MakeDivisionTable.fs
  3.  *
  4.  *  Purpose:  Make a division table in a handy written form.
  5.  *
  6.  *  Compile: fsc --codepage:949 MakeDivisionTable.fs
  7.  *
  8.  *  Execute: MakeDivisionTable 12345 32
  9.  *           MakeDivisionTable 500210 61
  10.  *           MakeDivisionTable 234 55
  11.  *
  12.  *     Date:  2010/07/15
  13.  *   Author:  PH Kim   [ pkim ((AT)) scripts.pe.kr ]
  14.  *)
  15. #light
  16. exception RuntimeError of string
  17. exception ValueError of string
  18. let BASE36 = "0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZ"
  19. let SPACE = "                                                          "
  20. let ULINE = "__________________________________________________________"
  21. let HIPHEN = "----------------------------------------------------------"
  22. let println s =
  23.     printfn "%O" s
  24. let print s =
  25.     printf "%O" s
  26. let printUsage dummy =
  27.     // print("Using: MakeDivisionTable [numerator] [denominator]")
  28.     // print("Make a division table in a handy written form.")
  29.     println "사용법: MakeDivisionTable [피제수] [제수]"
  30.     println "손으로 작성한 형태의 나눗셈 표를 만들어준다."
  31. let simplify v width =
        let mutable t = sprintf "%d" v
  32.     if (t.EndsWith ".0") then
  33.         t <- t.Substring(0, t.Length - 2)
  34.     let slen = t.Length
  35.     if slen < width then
  36.         t <- SPACE.Substring(0, width - slen) + t
  37.     t
  38. let getSuffix v =
  39.     let mutable t = v % 10
  40.     let mutable suffix = "은"
  41.     if "2459".IndexOf(sprintf "%d"  t) >= 0 then
  42.         suffix <- "는"
  43.     suffix
  44. let makeTable numer denom quotient =
  45.     let strNumer = sprintf "%d" numer
  46.     let strDenom = sprintf "%d" denom
  47.     let strQuotient = sprintf "%d" quotient
  48.     let lenN = strNumer.Length
  49.     let lenD = strDenom.Length
  50.     let lenQ = strQuotient.Length
  51.     let offsetLeft = 3 + lenD + 3
  52.     let spaces = "                                                                                 "
  53.     let mutable uline  = ULINE.Substring(0, lenN + 2)
  54.     let mutable sline  = HIPHEN.Substring(0, lenN)
  55.     let bias = lenN - lenQ
  56.     println(spaces.Substring(0, offsetLeft) + spaces.Substring(0, bias) + sprintf "%d" quotient)
  57.     println(spaces.Substring(0, offsetLeft - 2) + uline)
  58.     print("   " + strDenom + " ) " + strNumer)
  59.     let mutable strTmpR = strNumer.Substring(0, bias + 1)
  60.     let mutable tmpR = int strTmpR
  61.     let mutable tmpSub = 0
  62.     let mutable oneDigit = ""
  63.     for i in 0..(lenQ - 1) do
  64.         if (strQuotient.Substring(i, 1)) = "0" then
  65.             if i + 1 < lenQ then
  66.                 oneDigit <- (strNumer.Substring(bias + i + 1, 1))
  67.                 print(oneDigit)
  68.                 strTmpR <- strTmpR + oneDigit
  69.                 tmpR <- int strTmpR
  70.         else
  71.             println ""
  72.             tmpSub <- (int (strQuotient.Substring(i, 1))) * denom
  73.             println(spaces.Substring(0, offsetLeft) + simplify tmpSub  (bias + i + 1))
  74.             println(spaces.Substring(0, offsetLeft) + sline)
  75.             tmpR <- tmpR - tmpSub
  76.             if tmpR = 0 && i + 1 < lenQ then
  77.                 print(spaces.Substring(0, offsetLeft) + spaces.Substring(0, bias + i + 1))
  78.             else 
  79.                 print(spaces.Substring(0, offsetLeft) + (simplify tmpR (bias + i + 1))) 
  80.             strTmpR <- sprintf "%d" tmpR
  81.             if i + 1 < lenQ then
  82.                 oneDigit <- (strNumer.Substring(bias + i + 1, 1))
  83.                 if  (oneDigit.Length) > 0 then
  84.                     print(oneDigit)
  85.                 strTmpR <- strTmpR + oneDigit
  86.             tmpR <- int strTmpR
  87.     println ""
  88.     tmpR
  89. // Begin here
  90. let cmdArgs = System.Environment.GetCommandLineArgs()
  91. if (Array.length cmdArgs < 3 || "-h" = cmdArgs.[1]) then
  92.     printUsage 0
  93.     exit(1)
  94. let mutable a = 0
  95. let mutable b = 1
  96. try
  97.     a <- int (cmdArgs.[1])
  98.     b <- int (cmdArgs.[2])
  99. with
  100.     | ValueError e -> printfn "피제수: %s, 제수: %s" (cmdArgs.[1]) (cmdArgs.[2]);
  101.                       printfn "숫자 입력에 오류가 있습니다.";
  102.                       exit(1)
  103. if a <= 0 then
  104.     printf "피제수: %d" a
  105.     printf "피제수는 양의 정수라야 합니다."
  106.     exit(1)
  107. elif b <= 0 then
  108.     printf "제수: %d" b
  109.     printf "제수는 양의 정수라야 합니다."
  110.     exit(1)
  111. let q = a / b
  112. let r = a % b
  113. printf "나눗셈 %d ÷ %d 의 결과: " a b
  114. printf "몫: %d, " q
  115. printfn "나머지: %d" r
  116. printfn ""
  117. let k = makeTable a b q
  118. if k = r then
  119.     printfn "\n나머지: %d" k
  120. if k = 0 then
  121.     printfn "%d = %d x %d" a b q
  122.     printfn "%d%s %d의 배수(mupltiple)이다." a (getSuffix a) b
  123.     printfn "%d%s %d의 약수(divisor)이다." b (getSuffix b) a
  124. else
  125.     printfn "%d = %d x %d + %d" a b q r
  126.     printfn "%d%s %d의 배수(mupltiple)가 아니다." a (getSuffix a) b



컴파일> fsc --codepage:949   MakeDivisionTable.fs

실행> MakeDivisionTable.py 500210 61
나눗셈 500210 ÷ 61 의 결과: 몫: 8200, 나머지: 10

          8200
      ________
   61 ) 500210
         488
        ------
         122
         122
        ------
            10

나머지: 10
500210 = 61 x 8200 + 10
500210은 61의 배수(mupltiple)가 아니다.



 

Posted by Scripter
,

ASCII(애스키)란 American Standard Code for Information Interchange의 줄임글로서, 영문자에 기초한 문자 인코딩이다.  이 문자 인코딩에는 C0 제어문자(C0 control character)도 포함되어 있다.  ( 참고:  ASCII - Wikipedia, the free encyclopedia )

다음은  7bit ASCII 코드표를 만들어 보여주는 F# 소스 코드이다. 소스 코드 중에 진법변환에 필요한 함수

                atoi(string, radix)
                itoa(number, radix)

를 F# 코드로 자체 작성하여 사용하였다.

(아래의 소스는 Python 소스를 F# 소스로 일대일 변환 수정한 것이라서, F# 언어의 명령형 언어 특징을 위주로 작성되어 있다.)

  1. (*
  2.  *  Filename: MakeAsciiTable.fs
  3.  *            Make a table of ascii codes.
  4.  *
  5.  *  Compile: fsc MakeAsciiTable.fs
  6.  *  Execute: MakeAsciiTable
  7.  *
  8.  *      Date:  20010/07/15
  9.  *    Author:  PH Kim   [ pkim (AT) scripts.pe.kr ]
  10.  *)
  11. #light
  12. exception RuntimeError of string
  13. exception ValueError of string
  14. let BASE36 = "0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZ"
  15. let println s =
  16.     printfn "%O" s
  17. let print s =
  18.     printf "%O" s
  19. let printUsage dummy =
  20.     println "Usage: MakeAsciiTable"
  21.     println "Make a table of ascii codes."
  22. let itoa (num : int, radix : int) =
  23.    let mutable isNegative = false
  24.    let mutable numx = num
  25.    if num < 0 then
  26.       isNegative <- true
  27.       numx <- (-num)
  28.    let mutable arr = [  ]
  29.    let mutable q = numx
  30.    let mutable r = 0
  31.    while (q >= radix) do
  32.        r <- int (q % radix)
  33.        q <- int (q / radix)
  34.        arr <- List.append arr [ sprintf "%O" (BASE36.[r]) ]
  35.    arr <- List.append arr [ sprintf "%O" (BASE36.[q]) ]
  36.    if isNegative then
  37.       arr <- List.append arr [ "-" ]
  38.    arr <- List.rev arr
  39.    System.String.Join("", List.toArray arr)
  40. let atoi (s : string, radix : int) : int =
  41.     let mutable ret = 0
  42.     let mutable isNegative = false
  43.     let len = s.Length
  44.     let mutable valx = 0
  45.     let mutable c = s.[0]
  46.     if c = '-' then
  47.         isNegative <- true
  48.     elif (c >= '0' && c <= '9') then
  49.         ret <- (int c) - (int '0')
  50.     elif (c >= 'A' && c <= 'Z') then
  51.         ret <- int c - int 'A' + 10
  52.     elif (c >= 'a' && c <= 'z') then
  53.         ret <- int c - int 'a' + 10
  54.     if (ret >= radix) then
  55.         printfn "    Error: Can not read \"%s\" (as radix %d): %O is an invalid character!" s radix ret
  56.     for i = 1 to len - 1 do
  57.         c <- s.[i]
  58.         ret <- ret*radix
  59.         if (c >= '0' && c <= '9') then
  60.             valx <- int c - int '0'
  61.         elif (c >= 'A' && c <= 'Z') then
  62.             valx <- int c - int 'A' + 10
  63.         elif (c >= 'a' && c <= 'z') then
  64.             valx <- int c - int 'a' + 10
  65.         if (valx >= radix) then
  66.             printfn "    Error: Can not read \"%s\" (as radix %d): %O is an invalid character!" s radix c

  67.         ret <- ret + valx
  68.     if (isNegative) then
  69.         ret <- (-ret )
  70.     ret
  71. let asc = [
  72.     "NUL"; "SOH"; "STX"; "ETX"; "EOT";
  73.     "ENQ"; "ACK"; "BEL"; "BS"; "HT";
  74.     "LF"; "VT"; "FF"; "CR"; "SO";
  75.     "SI"; "DLE"; "DC1"; "DC2"; "DC3";
  76.     "DC4"; "NAK"; "SYN"; "ETB"; "CAN";
  77.     "EM"; "SUB"; "ESC"; "FS"; "GS";
  78.     "RS"; "US"; "Spc"
  79. ]
  80. let control = [
  81.     "NUL (null)";
  82.     "SOH (start of heading)";
  83.     "STX (start of text)";
  84.     "ETX (end of text)";
  85.     "EOT (end of transmission)";
  86.     "ENQ (enquiry)";
  87.     "ACK (acknowledge)";
  88.     "BEL (bell)";
  89.     "BS  (backspace)";
  90.     "TAB (horizontal tab)";
  91.     "LF  (line feed, NL new line)";
  92.     "VT  (vertical tab)";
  93.     "FF  (form feed, NP new page)";
  94.     "CR  (carriage return)";
  95.     "SO  (shift out)";
  96.     "SI  (shift in)";
  97.     "DLE (data link escape)";
  98.     "DC1 (device control 1)";
  99.     "DC2 (device control 2)";
  100.     "DC3 (device control 3)";
  101.     "DC4 (device control 4)";
  102.     "NAK (negative acknowledge)";
  103.     "SYN (synchronous idle)";
  104.     "ETB (end of trans. block)";
  105.     "CAN (cancel)";
  106.     "EM  (end of medium)";
  107.     "SUB (substitute, EOF end of file)";
  108.     "ESC (escape)";
  109.     "FS  (file separator)";
  110.     "GS  (group separator)";
  111.     "RS  (record separator)";
  112.     "US  (unit separator)";
  113. ]
  114. let makeTable dummy =
  115.     let mutable sbuf = ""
  116.     let mutable abuf = ""
  117.     let mutable tbuf = ""
  118.     let mutable c = 'a'
  119.     sbuf <- "    "
  120.     for i in 0..(8-1) do
  121.         sbuf <- sbuf +  "+----"
  122.     sbuf <- sbuf +  "+"
  123.     println(sbuf)
  124.     sbuf <- "    "
  125.     sbuf <- sbuf +  "| 0- "
  126.     sbuf <- sbuf +  "| 1- "
  127.     sbuf <- sbuf +  "| 2- "
  128.     sbuf <- sbuf +  "| 3- "
  129.     sbuf <- sbuf +  "| 4- "
  130.     sbuf <- sbuf +  "| 5- "
  131.     sbuf <- sbuf +  "| 6- "
  132.     sbuf <- sbuf +  "| 7- "
  133.     sbuf <- sbuf +  "|"
  134.     println(sbuf)
  135.     sbuf <- "+---"
  136.     for i in 0..(8-1) do
  137.         sbuf <- sbuf +  "+----"
  138.     sbuf <- sbuf +  "+"
  139.     println(sbuf)
  140.     for i in 0..(16-1) do
  141.         tbuf <- ""
  142.         sbuf <- itoa(i, 16)
  143.         tbuf <- tbuf +  "| " + sbuf + " "
  144.         for j in 0..(8-1) do
  145.             if j*16 + i <= 32 then
  146.                 abuf <- sprintf "| %-3s" (asc.[j*16 + i])
  147.             elif j*16 + i = 127 then
  148.                 abuf <- sprintf  "| %-3s" "DEL"
  149.             else
  150.                 c <- char (j*16 + i)
  151.                 abuf <- sprintf "|  %1c " c
  152.             tbuf <- tbuf + abuf
  153.         tbuf <- tbuf + "|"
  154.         println(tbuf)
  155.     sbuf <- "+---"
  156.     for i in 0..(8-1) do
  157.         sbuf <- sbuf + "+----"
  158.     sbuf <- sbuf + "+"
  159.     println(sbuf)
  160.     println("")
  161.     for i in 0..(16-1) do
  162.         tbuf <- sprintf "%-30s  %-34s" (control.[i]) (control.[i+16])
  163.         println(tbuf)
  164. // Begin here
  165. let cmdArgs = System.Environment.GetCommandLineArgs()
  166. if (Array.length cmdArgs > 1 && "-h" = cmdArgs.[1]) then
  167.     printUsage 0
  168.     exit(1)
  169. makeTable 0




컴파일> fsc MakeAsciiTable.fs

실행> MakeAsciiTable

   
    +----+----+----+----+----+----+----+----+
    | 0- | 1- | 2- | 3- | 4- | 5- | 6- | 7- |
+---+----+----+----+----+----+----+----+----+
| 0 | NUL| DLE| Spc|  0 |  @ |  P |  ` |  p |
| 1 | SOH| DC1|  ! |  1 |  A |  Q |  a |  q |
| 2 | STX| DC2|  " |  2 |  B |  R |  b |  r |
| 3 | ETX| DC3|  # |  3 |  C |  S |  c |  s |
| 4 | EOT| DC4|  $ |  4 |  D |  T |  d |  t |
| 5 | ENQ| NAK|  % |  5 |  E |  U |  e |  u |
| 6 | ACK| SYN|  & |  6 |  F |  V |  f |  v |
| 7 | BEL| ETB|  ' |  7 |  G |  W |  g |  w |
| 8 | BS | CAN|  ( |  8 |  H |  X |  h |  x |
| 9 | HT | EM |  ) |  9 |  I |  Y |  i |  y |
| A | LF | SUB|  * |  : |  J |  Z |  j |  z |
| B | VT | ESC|  + |  ; |  K |  [ |  k |  { |
| C | FF | FS |  , |  < |  L |  \ |  l |  | |
| D | CR | GS |  - |  = |  M |  ] |  m |  } |
| E | SO | RS |  . |  > |  N |  ^ |  n |  ~ |
| F | SI | US |  / |  ? |  O |  _ |  o | DEL|
+---+----+----+----+----+----+----+----+----+

NUL (null)                      DLE (data link escape)
SOH (start of heading)          DC1 (device control 1)
STX (start of text)             DC2 (device control 2)
ETX (end of text)               DC3 (device control 3)
EOT (end of transmission)       DC4 (device control 4)
ENQ (enquiry)                   NAK (negative acknowledge)
ACK (acknowledge)               SYN (synchronous idle)
BEL (bell)                      ETB (end of trans. block)
BS  (backspace)                 CAN (cancel)
TAB (horizontal tab)            EM  (end of medium)
LF  (line feed, NL new line)    SUB (substitute, EOF end of file)
VT  (vertical tab)              ESC (escape)
FF  (form feed, NP new page)    FS  (file separator)
CR  (carriage return)           GS  (group separator)
SO  (shift out)                 RS  (record separator)
SI  (shift in)                  US  (unit separator)




 

Posted by Scripter
,

컴퓨터 프로그래밍에서 꼭 알아두어야 할 주요 진법은 당연히 10진법, 2진법, 8진법, 16진법이다.
다음은  0 에서 15 까지의 정수를 10진법, 2진법, 8진법, 16진법의 표로 만들어 보여주는 F# 소스 코드이다. 진법 변환에 필요한 함수

        atoi(string, radix)
        itoa(number, radix)

를 F# 코드로 자체 작성하여 사용하였다.

(아래의 소스는 Python 소스를 F# 소스로 일대일 변환 수정한 것이라서, F# 언어의 명령형 언어 특징을 위주로 작성되어 있다.)

  1. (*
  2.  *  Filename: MakeRadixTable.fs
  3.  *            Show the radix table with 10-, 2-, 8-, 16-radices.
  4.  *
  5.  *  Compile: fsc MakeRadixTable.fs
  6.  *  Execute: MakeRadixTable
  7.  *
  8.  *      Date:  2010/07/15
  9.  *    Author:  PH Kim   [ pkim (AT) scripts.pe.kr ]
  10.  *)
  11. #light
  12. exception RuntimeError of string
  13. exception ValueError of string
  14. let BASE36 = "0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZ"
  15. let println s =
  16.     printfn "%O" s
  17. let print s =
  18.     printf "%O" s
  19. let printUsage dummy =
  20.     println "Usage: MakeRadixTable"
  21.     println "Show the radix table with 10-, 2-, 8-, 16-radices."
  22. let itoa (num : int, radix : int) =
  23.    let mutable isNegative = false
  24.    let mutable numx = num
  25.    if num < 0 then
  26.       isNegative <- true
  27.       numx <- (-num)
  28.    let mutable arr = [  ]
  29.    let mutable q = numx
  30.    let mutable r = 0
  31.    while (q >= radix) do
  32.        r <- int (q % radix)
  33.        q <- int (q / radix)
  34.        arr <- List.append arr [ sprintf "%O" (BASE36.[r]) ]
  35.    arr <- List.append arr [ sprintf "%O" (BASE36.[q]) ]
  36.    if isNegative then
  37.       arr <- List.append arr [ "-" ]
  38.    arr <- List.rev arr
  39.    System.String.Join("", List.toArray arr)
  40. let atoi (s : string, radix : int) : int =
  41.     let mutable ret = 0
  42.     let mutable isNegative = false
  43.     let len = s.Length
  44.     let mutable valx = 0
  45.     let mutable c = s.[0]
  46.     if c = '-' then
  47.         isNegative <- true
  48.     elif (c >= '0' && c <= '9') then
  49.         ret <- (int c) - (int '0')
  50.     elif (c >= 'A' && c <= 'Z') then
  51.         ret <- int c - int 'A' + 10
  52.     elif (c >= 'a' && c <= 'z') then
  53.         ret <- int c - int 'a' + 10
  54.     if (ret >= radix) then
  55.         printfn "    Error: Can not read \"%s\" (as radix %d): %O is an invalid character!" s radix ret
  56.     for i = 1 to len - 1 do
  57.         c <- s.[i]
  58.         ret <- ret*radix
  59.         if (c >= '0' && c <= '9') then
  60.             valx <- int c - int '0'
  61.         elif (c >= 'A' && c <= 'Z') then
  62.             valx <- int c - int 'A' + 10
  63.         elif (c >= 'a' && c <= 'z') then
  64.             valx <- int c - int 'a' + 10
  65.         if (valx >= radix) then
  66.             printfn "    Error: Can not read \"%s\" (as radix %d): %O is an invalid character!" s radix c
  67.         ret <- ret + valx
  68.     if (isNegative) then
  69.         ret <- (-ret )
  70.     ret
  71. let makeTable dummy =
  72.     let mutable sbuf = ""
  73.     let mutable abuf = ""
  74.     let mutable tbuf = ""
  75.     for i in 0..(4-1) do
  76.         sbuf <- sbuf + "+-------"
  77.     sbuf <- sbuf + "+"
  78.     println(sbuf)
  79.     sbuf <- "|  Dec"
  80.     sbuf <- sbuf +  "\t|   Bin"
  81.     sbuf <- sbuf +  "\t|  Oct"
  82.     sbuf <- sbuf +  "\t|  Hex  |"
  83.     println(sbuf)
  84.     sbuf <- ""
  85.     for i in 0..(4-1) do
  86.         sbuf <- sbuf +  "+-------"
  87.     sbuf <- sbuf +  "+"
  88.     println(sbuf)
  89.     for i in 0..(16-1) do
  90.         sbuf <- sprintf "|   %2d" i
  91.         abuf <- itoa(i, 2)
  92.         tbuf <- sprintf "\t|  %4s" abuf
  93.         sbuf <- sbuf +  tbuf
  94.         abuf <- itoa(i, 8)
  95.         tbuf <- sprintf "\t|   %2s" abuf
  96.         sbuf <- sbuf + tbuf
  97.         abuf <- itoa(i, 16)
  98.         tbuf <- sprintf "\t|    %-2s |"  abuf
  99.         sbuf <- sbuf +  tbuf
  100.         println(sbuf)
  101.     sbuf <- ""
  102.     for i in 0..(4-1) do
  103.         sbuf <- sbuf +  "+-------"
  104.     sbuf <- sbuf +  "+"
  105.     println(sbuf)
  106. // Begin here
  107. let cmdArgs = System.Environment.GetCommandLineArgs()
  108. if (Array.length cmdArgs > 1 && "-h" = cmdArgs.[1]) then
  109.     printUsage 0
  110.     exit(1)
  111. makeTable 0


컴파일> fsc MakeRadixTable.fs

실행> MakeRadixTable

+-------+-------+-------+-------+
|  Dec  |   Bin |  Oct  |  Hex  |
+-------+-------+-------+-------+
|    0  |     0 |    0  |    0  |
|    1  |     1 |    1  |    1  |
|    2  |    10 |    2  |    2  |
|    3  |    11 |    3  |    3  |
|    4  |   100 |    4  |    4  |
|    5  |   101 |    5  |    5  |
|    6  |   110 |    6  |    6  |
|    7  |   111 |    7  |    7  |
|    8  |  1000 |   10  |    8  |
|    9  |  1001 |   11  |    9  |
|   10  |  1010 |   12  |    A  |
|   11  |  1011 |   13  |    B  |
|   12  |  1100 |   14  |    C  |
|   13  |  1101 |   15  |    D  |
|   14  |  1110 |   16  |    E  |
|   15  |  1111 |   17  |    F  |
+-------+-------+-------+-------+




 

Posted by Scripter
,