1
1
mirror of https://github.com/sdiehl/wiwinwlh.git synced 2024-08-16 23:40:41 +03:00

Write more

This commit is contained in:
sdiehl 2020-01-18 06:20:33 +00:00
parent 47ca57da00
commit ef4f401237
5 changed files with 180 additions and 62 deletions

View File

@ -1,5 +1,19 @@
\documentclass[$if(fontsize)$$fontsize$,$endif$$if(lang)$$babel-lang$,$endif$$if(papersize)$$papersize$paper,$endif$$for(classoption)$$classoption$$sep$,$endfor$]{$documentclass$}
\usepackage[top=1cm, bottom=1.5cm, left=1.5cm, right=1.5cm]{geometry}
\usepackage{geometry}
\geometry{
a4paper,
total={21.59cm,27.94cm},
top=2.8cm,
bottom=2.1cm,
inner=1.91cm,
outer=6.68cm,
% For pdf
left=1.5cm,
right=1.5cm,
% For printing
%marginparwidth=4cm,
%marginparsep=0.8cm
}
$if(fontfamily)$
\usepackage[$for(fontfamilyoptions)$$fontfamilyoptions$$sep$,$endfor$]{$fontfamily$}
$else$

View File

@ -1,56 +0,0 @@
module Standalone where
-- Pretty Printer
import LLVM.General.Pretty (ppllvm)
-- AST
import qualified LLVM.General.AST as AST
import qualified LLVM.General.AST.Linkage as Linkage
import qualified LLVM.General.AST.Visibility as Visibility
import qualified LLVM.General.AST.CallingConvention as Convention
import Data.Text.Lazy.IO as TIO
astModule :: AST.Module
astModule = AST.Module
{ AST.moduleName = "example-llvm-module"
, AST.moduleDataLayout = Nothing
, AST.moduleTargetTriple = Nothing
, AST.moduleDefinitions =
[ AST.GlobalDefinition
(AST.Function
Linkage.External
Visibility.Default
Nothing
Convention.C
[]
(AST.IntegerType 8)
(AST.Name "f")
([AST.Parameter (AST.IntegerType 8) (AST.Name "x") []], False)
[]
Nothing
Nothing
0
Nothing
Nothing
[ AST.BasicBlock
(AST.Name "entry")
[]
(AST.Do
(AST.Ret
(Just
(AST.LocalReference
(AST.IntegerType 8)
(AST.Name "x")
)
)
[]
)
)
]
)
]
}
main :: IO ()
main = TIO.putStrLn (ppllvm astModule)

View File

@ -0,0 +1,53 @@
import Control.Monad.Except
import Data.ByteString.Char8 as BS
import LLVM.AST
import qualified LLVM.AST as AST
import LLVM.AST.Global
import LLVM.Context
import LLVM.Module
int :: Type
int = IntegerType 32
defAdd :: Definition
defAdd =
GlobalDefinition
functionDefaults
{ name = Name "add",
parameters =
( [ Parameter int (Name "a") [],
Parameter int (Name "b") []
],
False
),
returnType = int,
basicBlocks = [body]
}
where
body =
BasicBlock
(Name "entry")
[ Name "result"
:= Add
False -- no signed wrap
False -- no unsigned wrap
(LocalReference int (Name "a"))
(LocalReference int (Name "b"))
[]
]
(Do $ Ret (Just (LocalReference int (Name "result"))) [])
module_ :: AST.Module
module_ =
defaultModule
{ moduleName = "basic",
moduleDefinitions = [defAdd]
}
toLLVM :: AST.Module -> IO ()
toLLVM mod = withContext $ \ctx -> do
llvm <- withModuleFromAST ctx mod moduleLLVMAssembly
BS.putStrLn llvm
main :: IO ()
main = toLLVM module_

View File

@ -0,0 +1,37 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecursiveDo #-}
module Main where
import Data.Text.Lazy.IO as T
import LLVM.AST hiding (function)
import qualified LLVM.AST.Constant as C
import qualified LLVM.AST.Float as F
import qualified LLVM.AST.IntegerPredicate as P
import LLVM.AST.Type as AST
import LLVM.IRBuilder.Instruction
import LLVM.IRBuilder.Module
import LLVM.IRBuilder.Monad
simple :: Module
simple = buildModule "exampleModule" $ mdo
function "f" [(AST.i32, "a")] AST.i32 $ \[a] -> mdo
_entry <- block `named` "entry"
cond <- icmp P.EQ a (ConstantOperand (C.Int 32 0))
condBr cond ifThen ifElse
ifThen <- block
trVal <- add a (ConstantOperand (C.Int 32 0))
br ifExit
ifElse <- block `named` "if.else"
flVal <- add a (ConstantOperand (C.Int 32 0))
br ifExit
ifExit <- block `named` "if.exit"
r <- phi [(trVal, ifThen), (flVal, ifElse)]
ret r
function "plus" [(AST.i32, "x"), (AST.i32, "y")] AST.i32 $ \[x, y] -> do
_entry <- block `named` "entry2"
r <- add x y
ret r
main :: IO ()
main = print simple

View File

@ -15,7 +15,7 @@ This is the fifth major draft of this document since 2009.
* **[Kindle Version](http://dev.stephendiehl.com/hask/tutorial.mobi)**
License
--------
-------
This code and text are dedicated to the public domain. You can copy, modify,
distribute and perform the work, even for commercial purposes, all without
@ -29,6 +29,17 @@ always accepted for changes and additional content. This is a living document.
The only way this document will stay up to date is through the kindness of
readers like you and community patches and [pull requests](https://github.com/sdiehl/wiwinwlh) on Github.
Author
------
This text is authored and edited by Stephen Diehl.
* Web: www.stephendiehl.com
* Twitter: https://twitter.com/smdiehl
* Github: https://github.com/sdiehl
<hr/>
Basics
======
@ -1790,7 +1801,7 @@ it :: Num a => a
This rule may be deactivated with the ``NoMonomorphicRestriction`` extension,
see [below](#nomonomorphicrestriction).
See:
See:
* [Monomorphism Restriction](https://wiki.haskell.org/Monomorphism_restriction)
@ -5022,9 +5033,13 @@ iterateUntilM :: Monad m => (a -> Bool) -> (a -> m a) -> a -> m a
whileJust :: Monad m => m (Maybe a) -> (a -> m b) -> m [b]
```
<hr/>
Strings
=======
The string situation in Haskell is not great.
String
------
@ -6835,7 +6850,7 @@ See:
* [hint](http://hackage.haskell.org/package/mueval)
* [mueval](http://hackage.haskell.org/package/mueval)
</hr>
<hr/>
Testing
=======
@ -10794,6 +10809,12 @@ simple key-value store wrapped around the Map type.
~~~~ {.haskell include="src/28-databases/acid.hs"}
~~~~
Selda
-----
TODO
<hr/>
GHC
@ -11038,10 +11059,10 @@ associated with each package. For example to query the version of base library
currently used for compilation we can query from the `ghc-pkg` command:
```bash
$ ghc-pkg field base version
$ ghc-pkg field base version
version: 4.12.0.0
$ ghc-pkg field rts license
$ ghc-pkg field rts license
license: BSD-3-Clause
$ ghc-pkg field haskeline exposed-modules
@ -12958,6 +12979,52 @@ See:
* [repline](https://github.com/sdiehl/repline)
LLVM
----
Haskell has a rich set of LLVM bindings that can generate LLVM and JIT dynamic
code from inside of the Haskell runtime. This is especially useful for building
custom programming languages and compilers which need native performance. The
`llvm-hs` library is the de-factor standard for compiler construction in
Haskell. The `llvm-hs` library is split across two modules:
* llvm-hs-pure - Pure Haskell datatypes
* llvm-hs - Bindings to C++ framework for optimisation and JIT
The `llvm-hs` bindings allow us to construct LLVM abstract syntax tree by
manipulating a variety of Haskell datatypes. These datatypes all can be
serialised to the C++ bindings to construct the
~~~~ {.haskell include="src/30-languages/llvm-hs.hs"}
~~~~
This will generate the following LLVM module which can be pretty printed out:
```llvm
; ModuleID = 'basic'
source_filename = "<string>"
define i32 @add(i32 %a, i32 %b) {
entry:
%result = add i32 %a, %b
ret i32 %result
}
```
An alternative interface uses an IRBuilder monad which interactively constructs
up the LLVM AST using monadic combinators.
~~~~ {.haskell include="src/30-languages/llvm-irbuilder.hs"}
~~~~
See:
* [llvm-hs](https://hackage.haskell.org/package/llvm-hs)
* [llvm-hs-pure](https://hackage.haskell.org/package/llvm-hs-pure)
* [llvm-hs-examples](https://github.com/llvm-hs/llvm-hs-examples)
* [Kaleidoscope Tutorial](http://www.stephendiehl.com/llvm)
* [llvm-hs Github](https://github.com/llvm-hs)
</hr>
Template Haskell
@ -13063,6 +13130,9 @@ In this example we just spliced in the anti-quoted Haskell string in the printf
many other values to and from the quoted expressions including identifiers, numbers, and other quoted
expressions which implement the ``Lift`` type class.
GPU Kernels
-----------
For example now if we wanted programmatically generate the source for a CUDA kernel to run on a GPU we can
switch over the CUDA C dialect to emit the C code.