tags:

views:

91

answers:

2

I am writing a program in Haskell here it is the code

module Main
where
import IO
import Maybe
import Control.Monad.Reader
--il mio environment consiste in una lista di tuple/coppie chiave-valore
data Environment = Env {variables::[(String,String)]}deriving (Show)

fromEnvToPair :: Environment-> [(String,String)]
fromEnvToPair (Env e)= e

estrai' x d
|length x==0=[]
|otherwise=estrai x d
estrai (x:xs) d
| (x:xs)=="" =[]
| x== d=[]
| otherwise = x:(estrai  xs d)
--estrae da una stringa tutti i caratteri saino a d
conta'  x d n 
| length x==0 = 0
|otherwise = conta x d n 
conta (x:xs) d n
| x== d=n
| otherwise = (conta  xs d (n+1))
primo (a,b,c)=a
secondo (a,b,c)=b
terzo (a,b,c)=c

estraifrom x d n
|n>=(length x) =[]
| x!!n==d = []
|otherwise = x!!n:(estraifrom x d (n+1))

readerContent :: Reader Environment Environment
readerContent =do
content <- ask
return ( content)

-- resolve a template into a string
resolve :: [Char]-> Reader Environment (String)
resolve key= do
varValue <- asks (lookupVar key)
return $ maybe "" id varValue

maketuple x =(k,v,l) where
k= (estrai' x ':')--usare estrai'

v=estraifrom x ';' (conta' x ':' 1)
l= (length k)+(length v)+2 --è l'offset dovuto al; e al :
makecontext x
| length x==0 = []
| (elem ':' x)&&(elem ';' x)==False = []
|otherwise= (k,v):makecontext (drop l x) where
    t= maketuple x
    k= primo t
    v= secondo t
    l= terzo t



doRead filename = do
    bracket(openFile filename ReadMode) hClose(\h -> do 
        contents <- hGetContents h 
        return contents
        let cont=makecontext contents
        putStrLn (take 100 contents)
        return (contents))
--          putStrLn (snd (cont!!1)))
--          putStrLn (take 100 contents))


-- estrae i caratteri di una stringa dall'inizio fino al carattere di controllo
-- aggiungere parametri to the environment

-- estrae i caratteri di una stringa dall'inizio fino al carattere di controllo
-- aggiungere parametri to the environment



-- lookup a variable from the environment
lookupVar :: [Char] -> Environment -> Maybe String
lookupVar name env = lookup name (variables env)
lookup'  x t=[v| (k,v)<-t,k==x]





fromJust' :: Maybe a -> a
fromJust' (Just x) = x
fromJust' Nothing  = error "fromJust: Nothing"

main = do

file<- doRead "context.txt"-- leggo il contesto
let env= Env( makecontext file) -- lo converto in Environment
let c1= fromEnvToPair(runReader readerContent env)
putStrLn(fromJust'(lookupVar "user" env))
--putStrLn ((lookup' "user" (fromEnvToPair env))!!0)-- read the environment
--putStrLn ("user"++ (fst (c1!!1)))
putStrLn ("finito")
--putStrLn("contesto" ++ (snd(context!!1)))

What I want to do is reading a file formating the content and puting it in Environment, well it read the file and does all the other stuff only if in doRead there is the line putStrLn (take 100 contents) otherwise I can not take anithing, somebody knows why? I do not want to leave that line if I do not know why thanks in advance thanks in advance

A: 

I think the problem is laziness. The file handle is closed before that content is actually read. By taking and printing some of the content before closing the handle, you force it to load it before returning/closing the handle.

I suggest using the readFile function from System.IO.Strict. It loads the content stricly (non-lazy), and it also saves some pains working with file handles. You simply replace the call to doRead with readFile, as it has the same type signature.

jkramer
A: 

Using one of the Haskell parser libraries can make this kind of thing much less painful and error-prone. Here's an example of how to do this with Attoparsec:

module Main where

import Control.Applicative
import qualified Data.Map as M
import Data.Attoparsec (maybeResult)
import qualified Data.Attoparsec.Char8 as A
import qualified Data.ByteString.Char8 as B

type Environment = M.Map String String

spaces = A.many $ A.char ' '

upTo delimiter = B.unpack <$> A.takeWhile (A.notInClass $ delimiter : " ")
                          <* (spaces >> A.char delimiter >> spaces)

entry = (,) <$> upTo ':' <*> upTo ';'

environment :: A.Parser Environment
environment = M.fromList <$> A.sepBy entry A.endOfLine

parseEnvironment :: B.ByteString -> Maybe Environment
parseEnvironment = maybeResult . flip A.feed B.empty . A.parse environment

If we have a file context.txt:

user: somebody;
home: somewhere;
x: 1;
y: 2;
z: 3;

We can test the parser as follows:

*Main> Just env <- parseEnvironment <$> B.readFile "context.txt"
*Main> print $ M.lookup "user" env
Just "somebody"
*Main> print env
fromList [("home","somewhere"),("user","somebody"),("x","1"),("y","2"),("z","3")]

Note that I'm using a Map to represent the environment, as camcann suggested in a comment on your previous Reader monad question.

Travis Brown