[Haskell-cafe] translate imperative pseudo code into haskell

2013-08-09 Thread Joerg Fritsch
I would need some help to get to a reasonable function involving the DB
read, addition and multiplication.

 

for 0 = i  row dimension of A

 for 0 = j  column dimension of B

for 0 = k  column dimension of A = row dimension of B

   sum += (read A (i,k))* (read B(k,j))

 

 

I started like this but then somehow lost the compass:

 

main = do

   map my.read (map (\(x,y) - matrixA: ++ show row ++ : ++ show
column) [ (i, j, k) | i - [1..50], j - [1..20], k - [1..30] ]) 

 

Can you pls help?

 

--Joerg

 

 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] casting a into Maybe a

2013-07-27 Thread Joerg Fritsch
If I have the following type signature 
transMit :: Serialize a = Socket - POSIXTime - KEY - Maybe a - TPSQ - 
TMap a - IO ()


And the function is called with
transMit s now key newmsgs q m 
where newmsgs is whatever type a I get but _not_ a Maybe a

then I get the error 
Could not deduce (a ~ Maybe a)
from the context (Serialize a)

Can I somehow when I call transmit cast newmsgs into a Maybe newmsgs or so so 
that the function call fits the type signature? 

--Joerg


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] what is wrong w my IORef Word32 ?

2013-07-18 Thread Joerg Fritsch
All, what is wrong w the below code?

I get an type error related to the operation shiftL

import Data.Bits
import Data.Word
import Data.IORef

data Word32s = Word32s { x :: IORef Word32 }

bitfield :: Word32
bitfield = 0

mkbitfield :: Word32 - IO Word32s
mkbitfield i = do the_bf - newIORef i
  return (Word32s the_bf)

sLbitfield :: Integer - Word32s - IO ()
sLbitfield i (Word32s bf) = do modifyIORef bf (shiftL i)

main::IO()
main = do
 oper_bf - mkbitfield bitfield 
 sLbitfield 2 oper_bf



bf_003.hs:15:48:
Couldn't match type `Int' with `Word32'
Expected type: Word32 - Word32
  Actual type: Int - Word32
In the return type of a call of `shiftL'
In the second argument of `modifyIORef', namely `(shiftL i)'
In a stmt of a 'do' block: modifyIORef bf (shiftL i)

bf_003.hs:15:55:
Couldn't match expected type `Word32' with actual type `Integer'
In the first argument of `shiftL', namely `i'
In the second argument of `modifyIORef', namely `(shiftL i)'
In a stmt of a 'do' block: modifyIORef bf (shiftL i)



Thanks,
--Joerg


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] what is wrong w my IORef Word32 ?

2013-07-18 Thread Joerg Fritsch
Can I easily fix the modifyIORef statement by swapping something ?
--Joerg

On Jul 18, 2013, at 7:19 PM, Edward Z. Yang ezy...@mit.edu wrote:

 shiftL has the wrong type:  Bits a = a - Int - a
 so it is expecting the value in the IORef to be an Int.
 
 Edward
 
 Excerpts from Joerg Fritsch's message of Thu Jul 18 10:08:22 -0700 2013:
 All, what is wrong w the below code?
 
 I get an type error related to the operation shiftL
 
 import Data.Bits
 import Data.Word
 import Data.IORef
 
 data Word32s = Word32s { x :: IORef Word32 }
 
 bitfield :: Word32
 bitfield = 0
 
 mkbitfield :: Word32 - IO Word32s
 mkbitfield i = do the_bf - newIORef i
  return (Word32s the_bf)
 
 sLbitfield :: Integer - Word32s - IO ()
 sLbitfield i (Word32s bf) = do modifyIORef bf (shiftL i)
 
 main::IO()
 main = do
 oper_bf - mkbitfield bitfield 
 sLbitfield 2 oper_bf
 
 
 
 bf_003.hs:15:48:
Couldn't match type `Int' with `Word32'
Expected type: Word32 - Word32
  Actual type: Int - Word32
In the return type of a call of `shiftL'
In the second argument of `modifyIORef', namely `(shiftL i)'
In a stmt of a 'do' block: modifyIORef bf (shiftL i)
 
 bf_003.hs:15:55:
Couldn't match expected type `Word32' with actual type `Integer'
In the first argument of `shiftL', namely `i'
In the second argument of `modifyIORef', namely `(shiftL i)'
In a stmt of a 'do' block: modifyIORef bf (shiftL i)
 
 
 
 Thanks,
 --Joerg
 


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Design of a DSL in Haskell

2012-12-04 Thread Joerg Fritsch
Hi Tillmann,

is a shallow embedded DSL == an internal DSL and a deeply embedded DSL == an 
external DSL or the other way around?

--Joerg

On Dec 3, 2012, at 11:40 PM, Tillmann Rendel wrote:

 Hi,
 
 Joerg Fritsch wrote:
 I am working on a DSL that eventuyally would allow me to say:
 
 import language.cwmwl
 
 main = runCWMWL $ do
 
 eval (isFib::, 1000, ?BOOL)
 
 
 I have just started to work on the interpreter-function runCWMWL and I
 wonder whether it is possible to escape to real Haskell somehow (and
 how?) either inside ot outside the do-block.
 
 You can already use Haskell in your DSL. A simple example:
 
  main = runCWMWL $ do
eval (isFib::, 500 + 500, ?BOOL)
 
 The (+) operator is taken from Haskell, and it is available in your DSL 
 program. This use of Haskell is completely for free: You don't have to do 
 anything special with your DSL implementation to support it. I consider this 
 the main benefit of internal vs. external DSLs.
 
 
 A more complex example:
 
  main = runCWMWL $ do
foo - eval (isFib::, 1000, ?BOOL)
if foo
  then return 27
  else return 42
 
 Here, you are using the Haskell if-then-else expression to decide which DSL 
 program to run. Note that this example also uses (=) and return, so it only 
 works because your DSL is monadic. Beyond writing the Monad instance, you 
 don't have to do anything special to support this. In particular, you might 
 not need an additional embed function if you've already implemented return 
 from the Monad type class. I consider this the main benefit of the Monad type 
 class.
 
  Tillmann


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Design of a DSL in Haskell

2012-12-04 Thread Joerg Fritsch
Kim-Eeh, Tillmann,

I am interested in the definition of deep vs shallow embedded, even if it is 
not featured in the Fowler textbook. Fowler that is one textbook only and I 
am not focused on it. 

--Joerg


On Dec 5, 2012, at 2:59 AM, Kim-Ee Yeoh wrote:

 On Wed, Dec 5, 2012 at 8:32 AM, Tillmann Rendel 
 ren...@informatik.uni-marburg.de wrote:
 I mean internal == embedded, independently of deep vs. shallow, following 
 Martin Fowler [1].
 [1] http://martinfowler.com/bliki/DomainSpecificLanguage.html
 
 If I look here [2] I see:
 
 An internal DSL is just a particular idiom of writing code in the host 
 language. So a Ruby internal DSL is Ruby code, just written in particular 
 style which gives a more language-like feel. As such they are often called 
 Fluent Interfaces orEmbedded DSLs. An external DSL is a completely separate 
 language that is parsed into data that the host language can understand.
 
 Fowler places undue emphasis on the completely separate language, but other 
 than that, the correspondence is clear. I wonder how he thinks about C 
 implementing C? Or ghc implementing haskell in haskell? Would he say, Well, 
 clearly C and haskell are not DSLs, they are general purpose languages!?
 
 [2] http://martinfowler.com/bliki/DslQandA.html
 
 -- Kim-Ee
 
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Design of a DSL in Haskell

2012-12-03 Thread Joerg Fritsch
Thanks Brent,

my question is basically how the function embed would in practice be 
implemented.

I want to be able to take everything that my own language does not have from 
the host language, ideally so that I can say:

evalt - eval (isFib::, 1000, ?BOOL))
case evalt of
   Left Str - 
   Right Str -  


or so.

--Joerg

On Dec 3, 2012, at 4:04 PM, Brent Yorgey wrote:

 (Sorry, forgot to reply to the list initially; see conversation below.)
 
 On Mon, Dec 03, 2012 at 03:49:00PM +0100, Joerg Fritsch wrote:
 Brent,
 
 I believe that inside the do-block (that basically calls my
 interpreter) I cannot call any other Haskell function that are not
 recognized by my parser and interpreter.
 
 This seems to just require some sort of escape mechanism for
 embedding arbitrary Haskell code into your language.  For example a
 primitive
 
  embed :: a - CWMWL a
 
 (assuming CWMWL is the name of your monad).  Whether this makes sense,
 how to implement embed, etc. depends entirely on your language and
 interpreter.  
 
 However, as you imply below, this may or may not be possible depending
 on the type a.  In that case I suggest making embed a type class method.
 Something like
 
  class Embeddable a where
embed :: a - CWMWL a
 
 I still get the feeling, though, that I have not really understood
 your question.
 
 I am also trying to learn how I could preserve state from one line
 of code of my DSL to the next. I understand that inside the
 interpreter one would use a combination of the state monad and the
 reader monad, but could not find any non trivial example.
 
 Yes, you can use the state monad to preserve state from one line to
 the next.  I am not sure what you mean by using a combination of state
 and reader monads.  There is nothing magical about the combination.
 You would use state + reader simply if you had some mutable state as
 well as some read-only configuration to thread through your
 interpreter.
 
 xmonad is certainly a nontrivial example but perhaps it is a bit *too*
 nontrivial.  If I think of any other good examples I'll let you know.
 
 -Brent
 
 
 
 On Dec 3, 2012, at 1:23 PM, Brent Yorgey wrote:
 
 On Sun, Dec 02, 2012 at 03:01:46PM +0100, Joerg Fritsch wrote:
 This is probably a very basic question.
 
 I am working on a DSL that eventuyally would allow me to say:
 
 import language.cwmwl
 main = runCWMWL $ do
   eval (isFib::, 1000, ?BOOL)
 
 I have just started to work on the interpreter-function runCWMWL and I 
 wonder whether it is possible to escape to real Haskell somehow (and how?) 
 either inside ot outside the do-block.
 
 I don't think I understand the question.  The above already *is* real
 Haskell.  What is there to escape?
 
 I thought of providing a defautl-wrapper for some required prelude
 functions (such as print) inside my interpreter but I wonder if
 there are more elegant ways to co-loacate a DSL and Haskell without
 falling back to being a normal library only.
 
 I don't understand this sentence either.  Can you explain what you are
 trying to do in more detail?
 
 -Brent
 
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Design of a DSL in Haskell

2012-12-03 Thread Joerg Fritsch
The below is probably not a good example since it does not require a DSL but 
the principle is clear that I want to take things from teh host language that I 
do not have implemented (yet) in my DSL.

--Joerg

On Dec 3, 2012, at 4:25 PM, Joerg Fritsch wrote:

 Thanks Brent,
 
 my question is basically how the function embed would in practice be 
 implemented.
 
 I want to be able to take everything that my own language does not have from 
 the host language, ideally so that I can say:
 
 evalt - eval (isFib::, 1000, ?BOOL))
 case evalt of
Left Str - 
Right Str -  
 
 
 or so.
 
 --Joerg
 
 On Dec 3, 2012, at 4:04 PM, Brent Yorgey wrote:
 
 (Sorry, forgot to reply to the list initially; see conversation below.)
 
 On Mon, Dec 03, 2012 at 03:49:00PM +0100, Joerg Fritsch wrote:
 Brent,
 
 I believe that inside the do-block (that basically calls my
 interpreter) I cannot call any other Haskell function that are not
 recognized by my parser and interpreter.
 
 This seems to just require some sort of escape mechanism for
 embedding arbitrary Haskell code into your language.  For example a
 primitive
 
  embed :: a - CWMWL a
 
 (assuming CWMWL is the name of your monad).  Whether this makes sense,
 how to implement embed, etc. depends entirely on your language and
 interpreter.  
 
 However, as you imply below, this may or may not be possible depending
 on the type a.  In that case I suggest making embed a type class method.
 Something like
 
  class Embeddable a where
embed :: a - CWMWL a
 
 I still get the feeling, though, that I have not really understood
 your question.
 
 I am also trying to learn how I could preserve state from one line
 of code of my DSL to the next. I understand that inside the
 interpreter one would use a combination of the state monad and the
 reader monad, but could not find any non trivial example.
 
 Yes, you can use the state monad to preserve state from one line to
 the next.  I am not sure what you mean by using a combination of state
 and reader monads.  There is nothing magical about the combination.
 You would use state + reader simply if you had some mutable state as
 well as some read-only configuration to thread through your
 interpreter.
 
 xmonad is certainly a nontrivial example but perhaps it is a bit *too*
 nontrivial.  If I think of any other good examples I'll let you know.
 
 -Brent
 
 
 
 On Dec 3, 2012, at 1:23 PM, Brent Yorgey wrote:
 
 On Sun, Dec 02, 2012 at 03:01:46PM +0100, Joerg Fritsch wrote:
 This is probably a very basic question.
 
 I am working on a DSL that eventuyally would allow me to say:
 
 import language.cwmwl
 main = runCWMWL $ do
   eval (isFib::, 1000, ?BOOL)
 
 I have just started to work on the interpreter-function runCWMWL and I 
 wonder whether it is possible to escape to real Haskell somehow (and 
 how?) either inside ot outside the do-block.
 
 I don't think I understand the question.  The above already *is* real
 Haskell.  What is there to escape?
 
 I thought of providing a defautl-wrapper for some required prelude
 functions (such as print) inside my interpreter but I wonder if
 there are more elegant ways to co-loacate a DSL and Haskell without
 falling back to being a normal library only.
 
 I don't understand this sentence either.  Can you explain what you are
 trying to do in more detail?
 
 -Brent
 
 
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Design of a DSL in Haskell

2012-12-02 Thread Joerg Fritsch
This is probably a very basic question.

I am working on a DSL that eventuyally would allow me to say:

import language.cwmwl
main = runCWMWL $ do
eval (isFib::, 1000, ?BOOL)

I have just started to work on the interpreter-function runCWMWL and I wonder 
whether it is possible to escape to real Haskell somehow (and how?) either 
inside ot outside the do-block.

I thought of providing a defautl-wrapper for some required prelude functions 
(such as print) inside my interpreter but I wonder if there are more elegant 
ways to co-loacate a DSL and Haskell without falling back to being a normal 
library only.

--Joerg

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Design of a DSL in Haskell

2012-12-02 Thread Joerg Fritsch
Rusi,

I have read Fowler's book.(that is focusing on Java by the way) and could not 
find the answer there, I think it is a typical textbook.
I think this is a good start by the way: 
http://www.cse.chalmers.se/edu/year/2011/course/TIN321/lectures/bnfc-tutorial.html

--Joerg


On Dec 2, 2012, at 5:45 PM, Rustom Mody wrote:

 On Sun, Dec 2, 2012 at 7:31 PM, Joerg Fritsch frit...@joerg.cc wrote:
 This is probably a very basic question.
 
 I am working on a DSL that eventuyally would allow me to say:
 
 
 import language.cwmwl
 main = runCWMWL $ do
 eval (isFib::, 1000, ?BOOL)
 
 I have just started to work on the interpreter-function runCWMWL and I wonder 
 whether it is possible to escape to real Haskell somehow (and how?) either 
 inside ot outside the do-block.
 
 I thought of providing a defautl-wrapper for some required prelude functions 
 (such as print) inside my interpreter but I wonder if there are more elegant 
 ways to co-loacate a DSL and Haskell without falling back to being a normal 
 library only.
 
 --Joerg
 
 
 
 +1
 I am also interested in the DSL-in-Haskell possibilities
 
 [I am assuming Joerg that you're familiar with the basic ideas and 
 terminology like
 http://martinfowler.com/bliki/DomainSpecificLanguage.html and the links 
 therein]
 
 Rusi
 
 -- 
 http://www.the-magus.in
 http://blog.languager.org
 
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe