Skip to content

Instantly share code, notes, and snippets.

@fredyr
Created July 2, 2014 06:33
Show Gist options
  • Save fredyr/ea76338af4a5247bc7cc to your computer and use it in GitHub Desktop.
Save fredyr/ea76338af4a5247bc7cc to your computer and use it in GitHub Desktop.
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
import Control.Monad (void)
import Ivory.Language
import Ivory.Compile.C.CmdlineFrontend
import Ivory.Compile.C.Modules
[ivory|
struct Cool {
idx :: Stored Uint32
; arr :: Array 10 (Stored Uint32)
; value :: Stored IFloat
}
|]
degrees :: (Fractional a) => a -> a
degrees x = x * 57.295779513082320876798154814105
computerz :: Def ('[IFloat, IFloat, IFloat] :-> IFloat)
computerz = proc "computerz" $ \a b c -> requires (c /=? 0) $ body $ do
a' <- assign $ degrees a
b' <- assign $ degrees b
diff <- assign $ a' - b'
ret $ diff / c
clearCool :: Def ('[Ref a (Struct "Cool")] :-> ())
clearCool = proc "clear_cool" $ \s -> body $ do
x <- deref (s~>idx)
store ((s~>arr) ! (0 :: Ix 10)) 12
-- init all values
arrayMap (\ix -> store ((s~>arr) ! (ix :: Ix 10)) 4)
store (s~>value) 3.1415927
store (s~>idx) (x + 1)
cmodule :: Module
cmodule = package "Stuff" $ do
defStruct (Proxy :: Proxy "Cool")
incl computerz
incl clearCool
runIt :: IO ()
runIt = void $ runCompiler [cmodule] initialOpts { stdOut = True }
@fredyr
Copy link
Author

fredyr commented Jul 2, 2014

// Stuff.c

#include "Stuff.h"
float computerz(float n_var0, float n_var1, float n_var2)
{
    REQUIRES((bool) (n_var2 != 0.0f));

    float n_let0 = (float) (n_var0 * 57.29578f);
    float n_let1 = (float) (n_var1 * 57.29578f);
    float n_let2 = (float) (n_let0 - n_let1);

    return (float) (n_let2 / n_var2);
}
void clear_cool(struct Cool* n_var0)
{
    uint32_t n_deref0 = n_var0->idx;

    *&n_var0->arr[(int32_t) 0 % 10] = (uint32_t) 12U;
    COMPILER_ASSERTS((bool) ((bool) ((int32_t) 0 < (int32_t) 10) &&
                             (bool) ((int32_t) -(int32_t) 1 <= (int32_t) 0)));
    COMPILER_ASSERTS((bool) ((bool) ((int32_t) 9 < (int32_t) 10) &&
                             (bool) ((int32_t) -(int32_t) 1 <= (int32_t) 9)));
    for (int32_t n_ix1 = (int32_t) ((int32_t) 0 % (int32_t) 10); n_ix1 <=
         (int32_t) ((int32_t) 9 % (int32_t) 10); n_ix1++) {
        *&n_var0->arr[n_ix1] = (uint32_t) 4U;
    }
    *&n_var0->value = 3.1415927f;
    *&n_var0->idx = (uint32_t) (n_deref0 + (uint32_t) 1U);
}

// Stuff.h

#include "ivory.h"
struct Cool {
    uint32_t idx;
    uint32_t arr[10U];
    float value;
} __attribute__((__packed__));
float computerz(float n_var0, float n_var1, float n_var2);
void clear_cool(struct Cool* n_var0);

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment